[Git][ghc/ghc][wip/T26415] Fix tabs in string gaps (#26415)
Brandon Chinn pushed to branch wip/T26415 at Glasgow Haskell Compiler / GHC Commits: e6dcdd56 by Brandon Chinn at 2025-09-16T21:58:14-07:00 Fix tabs in string gaps (#26415) - - - - - 5 changed files: - compiler/GHC/Parser/Lexer.x - compiler/GHC/Parser/Lexer/String.x - + testsuite/tests/parser/should_run/T26415.hs - + testsuite/tests/parser/should_run/T26415.stdout - testsuite/tests/parser/should_run/all.T Changes: ===================================== compiler/GHC/Parser/Lexer.x ===================================== @@ -145,7 +145,7 @@ import GHC.Parser.String $unispace = \x05 -- Trick Alex into handling Unicode. See Note [Unicode in Alex]. $nl = [\n\r\f] $space = [\ $unispace] -$whitechar = [$nl \v $space] +$whitechar = [$nl \t \v $space] $white_no_nl = $whitechar # \n -- TODO #8424 $tab = \t @@ -248,7 +248,7 @@ haskell :- -- Alex "Rules" -- everywhere: skip whitespace -$white_no_nl+ ; +($white_no_nl | \t)+ ; $tab { warnTab } -- Everywhere: deal with nested comments. We explicitly rule out ===================================== compiler/GHC/Parser/Lexer/String.x ===================================== @@ -25,7 +25,7 @@ import GHC.Utils.Panic (panic) $unispace = \x05 -- Trick Alex into handling Unicode. See Note [Unicode in Alex]. $nl = [\n\r\f] $space = [\ $unispace] -$whitechar = [$nl \v $space] +$whitechar = [$nl \t \v $space] $tab = \t $ascdigit = 0-9 ===================================== testsuite/tests/parser/should_run/T26415.hs ===================================== @@ -0,0 +1,6 @@ +{-# LANGUAGE MultilineStrings #-} + +main :: IO () +main = do + print "\ \" + print """\ \""" ===================================== testsuite/tests/parser/should_run/T26415.stdout ===================================== @@ -0,0 +1 @@ +"" ===================================== testsuite/tests/parser/should_run/all.T ===================================== @@ -27,6 +27,7 @@ test('RecordDotSyntax4', [extra_files(['RecordDotSyntaxA.hs'])], multimod_compil test('RecordDotSyntax5', normal, compile_and_run, ['']) test('ListTuplePunsConstraints', extra_files(['ListTuplePunsConstraints.hs']), ghci_script, ['ListTuplePunsConstraints.script']) test('T25937', normal, compile_and_run, ['']) +test('T26415', normal, compile_and_run, ['']) # Multiline strings test('MultilineStrings', normal, compile_and_run, ['']) View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e6dcdd56008c3da6573fb672c6657424... -- View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/e6dcdd56008c3da6573fb672c6657424... You're receiving this email because of your account on gitlab.haskell.org.
participants (1)
-
Brandon Chinn (@brandonchinn178)