Brandon Chinn pushed to branch wip/T26415 at Glasgow Haskell Compiler / GHC

Commits:

5 changed files:

Changes:

  • compiler/GHC/Parser/Lexer.x
    ... ... @@ -145,7 +145,7 @@ import GHC.Parser.String
    145 145
     $unispace    = \x05 -- Trick Alex into handling Unicode. See Note [Unicode in Alex].
    
    146 146
     $nl          = [\n\r\f]
    
    147 147
     $space       = [\ $unispace]
    
    148
    -$whitechar   = [$nl \v $space]
    
    148
    +$whitechar   = [$nl \t \v $space]
    
    149 149
     $white_no_nl = $whitechar # \n -- TODO #8424
    
    150 150
     $tab         = \t
    
    151 151
     
    
    ... ... @@ -248,7 +248,7 @@ haskell :-
    248 248
     -- Alex "Rules"
    
    249 249
     
    
    250 250
     -- everywhere: skip whitespace
    
    251
    -$white_no_nl+ ;
    
    251
    +($white_no_nl # \t)+ ;
    
    252 252
     $tab          { warnTab }
    
    253 253
     
    
    254 254
     -- Everywhere: deal with nested comments.  We explicitly rule out
    

  • compiler/GHC/Parser/Lexer/String.x
    ... ... @@ -25,7 +25,7 @@ import GHC.Utils.Panic (panic)
    25 25
     $unispace    = \x05 -- Trick Alex into handling Unicode. See Note [Unicode in Alex].
    
    26 26
     $nl          = [\n\r\f]
    
    27 27
     $space       = [\ $unispace]
    
    28
    -$whitechar   = [$nl \v $space]
    
    28
    +$whitechar   = [$nl \t \v $space]
    
    29 29
     $tab         = \t
    
    30 30
     
    
    31 31
     $ascdigit  = 0-9
    

  • testsuite/tests/parser/should_run/T26415.hs
    1
    +{-# LANGUAGE MultilineStrings #-}
    
    2
    +
    
    3
    +main :: IO ()
    
    4
    +main = do
    
    5
    +	print "\	\"
    
    6
    +	print """\	\"""

  • testsuite/tests/parser/should_run/T26415.stdout
    1
    +""

  • testsuite/tests/parser/should_run/all.T
    ... ... @@ -27,6 +27,7 @@ test('RecordDotSyntax4', [extra_files(['RecordDotSyntaxA.hs'])], multimod_compil
    27 27
     test('RecordDotSyntax5', normal, compile_and_run, [''])
    
    28 28
     test('ListTuplePunsConstraints', extra_files(['ListTuplePunsConstraints.hs']), ghci_script, ['ListTuplePunsConstraints.script'])
    
    29 29
     test('T25937', normal, compile_and_run, [''])
    
    30
    +test('T26415', normal, compile_and_run, [''])
    
    30 31
     
    
    31 32
     # Multiline strings
    
    32 33
     test('MultilineStrings', normal, compile_and_run, [''])