[Git][ghc/ghc][wip/multiline-strings] Address feedback
Brandon Chinn (@brandonchinn178)
gitlab at gitlab.haskell.org
Tue Jul 23 15:22:19 UTC 2024
Brandon Chinn pushed to branch wip/multiline-strings at Glasgow Haskell Compiler / GHC
Commits:
bdbda97a by Brandon Chinn at 2024-07-23T07:53:13-07:00
Address feedback
- - - - -
2 changed files:
- compiler/GHC/Parser/String.hs
- testsuite/tests/perf/compiler/all.T
Changes:
=====================================
compiler/GHC/Parser/String.hs
=====================================
@@ -112,6 +112,7 @@ lexString strType getChar initialLoc = go initialState initialLoc
-- reached EOF before finding end of string
Nothing -> Left $ BadCharInitialLex loc0 (hasSQuote getChar s)
+{-# INLINE lexString #-}
checkDelimiter :: LexStringType -> GetChar loc -> loc -> Maybe loc
checkDelimiter strType getChar loc0 =
@@ -124,10 +125,12 @@ checkDelimiter strType getChar loc0 =
('"', loc2) <- getChar loc1
('"', loc3) <- getChar loc2
Just loc3
+{-# INLINE checkDelimiter #-}
-- | A helper for adding the given character to the lexed string.
addChar :: Char -> LexStringState loc -> LexStringState loc
addChar c s = s{stringAcc = c : stringAcc s}
+{-# INLINE addChar #-}
-- | Return whether the string we've parsed so far contains any smart quotes.
hasSQuote :: GetChar loc -> LexStringState loc -> ContainsSmartQuote loc
@@ -143,6 +146,7 @@ hasSQuote getChar s
case getChar loc of
Just (c, loc') -> Just ((c, loc), loc')
Nothing -> Nothing
+{-# INLINE hasSQuote #-}
-- | After parsing a backslash and a space character, consume the rest of
-- the string gap and return the next location.
@@ -155,6 +159,7 @@ collapseStringGap getChar s = go
Just (c0, loc1) | is_space c0 -> go loc1
Just _ -> Left $ BadCharInitialLex loc0 (hasSQuote getChar s)
Nothing -> Left $ UnexpectedEOF loc0 (hasSQuote getChar s)
+{-# INLINE collapseStringGap #-}
-- | See Note [Multiline string literals]
parseLeadingWS :: GetChar loc -> LexStringState loc -> loc -> (LexStringState loc, loc)
@@ -179,6 +184,7 @@ parseLeadingWS getChar = go 0
applyN :: Int -> (a -> a) -> a -> a
applyN n f x0 = iterate f x0 !! n
+{-# INLINE parseLeadingWS #-}
data StringLexError loc
= UnexpectedEOF !loc !(ContainsSmartQuote loc)
@@ -256,6 +262,7 @@ resolveEscapeCharacter getChar loc0 = do
_ ->
pure (chr x, loc)
parseNum (toDigit c1) loc2
+{-# INLINE resolveEscapeCharacter #-}
parseLongEscape :: GetChar loc -> Char -> loc -> Maybe (Char, loc)
parseLongEscape getChar c0 loc1 = listToMaybe $ mapMaybe tryParse longEscapeCodes
@@ -309,6 +316,7 @@ parseLongEscape getChar c0 loc1 = listToMaybe $ mapMaybe tryParse longEscapeCode
, ("SP", '\SP')
, ("DEL", '\DEL')
]
+{-# INLINE parseLongEscape #-}
-- -----------------------------------------------------------------------------
-- Unicode Smart Quote detection (#21843)
=====================================
testsuite/tests/perf/compiler/all.T
=====================================
@@ -764,6 +764,8 @@ test ('T24582',
['-O'])
test ('MultilineStringsPerf',
- [ collect_compiler_stats('peak_megabytes_allocated',20) ],
+ [ collect_compiler_stats('peak_megabytes_allocated', 20),
+ collect_compiler_stats('bytes allocated', 5),
+ ],
compile,
['-O'])
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bdbda97a21eac55a88276e0b602453f0c8dc55bc
--
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/bdbda97a21eac55a88276e0b602453f0c8dc55bc
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/20240723/0d8fa8b8/attachment-0001.html>
More information about the ghc-commits
mailing list