[Git][ghc/ghc][master] Make Unicode brackets opening/closing tokens (#18225)

Marge Bot gitlab at gitlab.haskell.org
Sun May 24 19:23:07 UTC 2020



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
cd339ef0 by Joshua Price at 2020-05-24T15:22:56-04:00
Make Unicode brackets opening/closing tokens (#18225)

The tokens `[|`, `|]`, `(|`, and `|)` are opening/closing tokens as
described in GHC Proposal #229. This commit makes the unicode
variants (`⟦`, `⟧`, `⦇`, and `⦈`) act the same as their ASCII
counterparts.

- - - - -


5 changed files:

- compiler/GHC/Parser/Lexer.x
- + testsuite/tests/parser/unicode/T18225A.hs
- + testsuite/tests/parser/unicode/T18225B.hs
- + testsuite/tests/parser/unicode/T18225B.stderr
- testsuite/tests/parser/unicode/all.T


Changes:

=====================================
compiler/GHC/Parser/Lexer.x
=====================================
@@ -564,11 +564,11 @@ $tab          { warnTab }
 --
 -- The precise rules are as follows:
 --
---  * Identifiers, literals, and opening brackets (, (#, [, [|, [||, [p|, [e|,
---    [t|, {, are considered "opening tokens". The function followedByOpeningToken
---    tests whether the next token is an opening token.
+--  * Identifiers, literals, and opening brackets (, (#, (|, [, [|, [||, [p|,
+--    [e|, [t|, {, ⟦, ⦇, are considered "opening tokens". The function
+--    followedByOpeningToken tests whether the next token is an opening token.
 --
---  * Identifiers, literals, and closing brackets ), #), ], |], },
+--  * Identifiers, literals, and closing brackets ), #), |), ], |], }, ⟧, ⦈,
 --    are considered "closing tokens". The function precededByClosingToken tests
 --    whether the previous token is a closing token.
 --
@@ -1068,6 +1068,8 @@ followedByOpeningToken _ _ _ (AI _ buf)
         ('\"', _) -> True
         ('\'', _) -> True
         ('_', _) -> True
+        ('⟦', _) -> True
+        ('⦇', _) -> True
         (c, _) -> isAlphaNum c
 
 -- See Note [Whitespace-sensitive operator parsing]
@@ -1080,6 +1082,8 @@ precededByClosingToken _ (AI _ buf) _ _ =
     '\"' -> True
     '\'' -> True
     '_' -> True
+    '⟧' -> True
+    '⦈' -> True
     c -> isAlphaNum c
 
 {-# INLINE nextCharIs #-}


=====================================
testsuite/tests/parser/unicode/T18225A.hs
=====================================
@@ -0,0 +1,13 @@
+{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE UnicodeSyntax #-}
+
+module T18225A where
+
+(!) :: IO a -> b -> b
+(!) _ = id
+
+test1 :: Int
+test1 = $⟦1⟧
+
+test2 :: Int
+test2 = ⟦2⟧!2


=====================================
testsuite/tests/parser/unicode/T18225B.hs
=====================================
@@ -0,0 +1,11 @@
+{-# LANGUAGE Arrows #-}
+{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE UnicodeSyntax #-}
+
+module T18225B where
+
+f :: (a, (b, c)) -> b
+f (_, (x, _)) = x
+
+test :: a -> a
+test = proc x -> ⦇f⦈$([|x|])


=====================================
testsuite/tests/parser/unicode/T18225B.stderr
=====================================
@@ -0,0 +1 @@
+T18225B.hs:11:23: Parse error in command: [| x |]


=====================================
testsuite/tests/parser/unicode/all.T
=====================================
@@ -28,3 +28,5 @@ test('T10907', normal, compile, [''])
 test('T7650', normal, compile, [''])
 
 test('brackets', normal, compile, [''])
+test('T18225A', normal, compile, [''])
+test('T18225B', normal, compile_fail, [''])



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cd339ef0e8ce940902df79ed1d93b3af50ea6f77

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cd339ef0e8ce940902df79ed1d93b3af50ea6f77
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/20200524/7a9e6cc6/attachment-0001.html>


More information about the ghc-commits mailing list