Skip to content

Commit

Permalink
Modifier letter in middle of identifier is ok
Browse files Browse the repository at this point in the history
Refactoring only. Cleanup some loose ends from #10196.

Initially the idea was to only allow modifier letters at the end of
identifiers. Since we later decided to allow modifier letters also in
the middle of identifiers (because not doing so would not fix the
regression completely), the names `suffix` and `okIdSuffixChar` don't
seem appropriate anymore.

Remove TODO. Move test from should_fail to should_compile.
  • Loading branch information
thomie committed Feb 19, 2016
1 parent 2f733b3 commit d738e66
Show file tree
Hide file tree
Showing 6 changed files with 12 additions and 25 deletions.
14 changes: 3 additions & 11 deletions compiler/basicTypes/Lexeme.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,7 +28,6 @@ module Lexeme (
) where

import FastString
import Util ((<||>))

import Data.Char
import qualified Data.Set as Set
Expand Down Expand Up @@ -183,8 +182,7 @@ okConSymOcc str = all okSymChar str &&
-- but not worrying about case or clashing with reserved words?
okIdOcc :: String -> Bool
okIdOcc str
-- TODO. #10196. Only allow modifier letters in the suffix of an identifier.
= let hashes = dropWhile (okIdChar <||> okIdSuffixChar) str in
= let hashes = dropWhile okIdChar str in
all (== '#') hashes -- -XMagicHash allows a suffix of hashes
-- of course, `all` says "True" to an empty list

Expand All @@ -194,19 +192,13 @@ okIdChar :: Char -> Bool
okIdChar c = case generalCategory c of
UppercaseLetter -> True
LowercaseLetter -> True
OtherLetter -> True
TitlecaseLetter -> True
ModifierLetter -> True -- See #10196
OtherLetter -> True
DecimalNumber -> True
OtherNumber -> True
_ -> c == '\'' || c == '_'

-- | Is this character acceptable in the suffix of an identifier.
-- See alexGetByte in Lexer.x
okIdSuffixChar :: Char -> Bool
okIdSuffixChar c = case generalCategory c of
ModifierLetter -> True -- See #10196
_ -> False

-- | Is this character acceptable in a symbol (after the first char)?
-- See alexGetByte in Lexer.x
okSymChar :: Char -> Bool
Expand Down
9 changes: 4 additions & 5 deletions compiler/parser/Lexer.x
Original file line number Diff line number Diff line change
Expand Up @@ -155,9 +155,8 @@ $binit = 0-1
$octit = 0-7
$hexit = [$decdigit A-F a-f]

$suffix = \x07 -- Trick Alex into handling Unicode. See alexGetByte.
-- TODO #10196. Only allow modifier letters in the suffix of an identifier.
$idchar = [$small $large $digit $suffix \']
$modifier = \x07 -- Trick Alex into handling Unicode. See alexGetByte.
$idchar = [$small $large $digit $modifier \']

$pragmachar = [$small $large $digit]

Expand Down Expand Up @@ -1875,7 +1874,7 @@ alexGetByte (AI loc s)
symbol = '\x04'
space = '\x05'
other_graphic = '\x06'
suffix = '\x07'
modifier = '\x07'
adj_c
| c <= '\x06' = non_graphic
Expand All @@ -1892,7 +1891,7 @@ alexGetByte (AI loc s)
UppercaseLetter -> upper
LowercaseLetter -> lower
TitlecaseLetter -> upper
ModifierLetter -> suffix -- see #10196
ModifierLetter -> modifier -- see #10196
OtherLetter -> lower -- see #1103
NonSpacingMark -> other_graphic
SpacingCombiningMark -> other_graphic
Expand Down
5 changes: 5 additions & 0 deletions testsuite/tests/parser/should_compile/T10196.hs
Original file line number Diff line number Diff line change
Expand Up @@ -11,3 +11,8 @@ f =
xᵪ = xᵢ
xᵣ = xᵪ
in xᵣ

-- Modifier letters are also allowed in the middle of an identifier.
-- This should not be lexed as 2 separate identifiers.
xᵦx :: Int
xᵦx = 1
6 changes: 0 additions & 6 deletions testsuite/tests/parser/should_fail/T10196Fail3.hs

This file was deleted.

2 changes: 0 additions & 2 deletions testsuite/tests/parser/should_fail/T10196Fail3.stderr

This file was deleted.

1 change: 0 additions & 1 deletion testsuite/tests/parser/should_fail/all.T
Original file line number Diff line number Diff line change
Expand Up @@ -91,6 +91,5 @@ test('T8506', normal, compile_fail, [''])
test('T9225', normal, compile_fail, [''])
test('T10196Fail1', normal, compile_fail, [''])
test('T10196Fail2', normal, compile_fail, [''])
test('T10196Fail3', expect_broken(10196), compile_fail, [''])
test('T10498a', normal, compile_fail, [''])
test('T10498b', normal, compile_fail, [''])

0 comments on commit d738e66

Please sign in to comment.