[commit: ghc] master: Remove ~# from surface syntax (5b82ee6)

git at git.haskell.org git at git.haskell.org
Sun Jun 3 03:22:49 UTC 2018


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/5b82ee695e1dbbe355c775e265521c4c3ee8cdbb/ghc

>---------------------------------------------------------------

commit 5b82ee695e1dbbe355c775e265521c4c3ee8cdbb
Author: David Feuer <david.feuer at gmail.com>
Date:   Sat Jun 2 21:24:04 2018 -0400

    Remove ~# from surface syntax
    
    For some reason, it seems that the `ConstraintKinds` commit
    introduced `~#` into Haskell syntax, in a pretty broken manner.
    Unless and until we have an actual story for unboxed equality,
    it doesn't make sense to expose it. Moreover, the way it was
    donet was wrong enough and small enough that it will probably be
    easier to start over if we do that. Yank it out.
    
    Reviewers: bgamari, RyanGlScott
    
    Reviewed By: RyanGlScott
    
    Subscribers: RyanGlScott, rwbarton, thomie, mpickering, carter
    
    GHC Trac Issues: #15209
    
    Differential Revision: https://phabricator.haskell.org/D4763


>---------------------------------------------------------------

5b82ee695e1dbbe355c775e265521c4c3ee8cdbb
 compiler/basicTypes/RdrName.hs   | 2 +-
 compiler/parser/ApiAnnotation.hs | 3 +--
 compiler/parser/Lexer.x          | 2 --
 compiler/parser/Parser.y         | 3 ---
 4 files changed, 2 insertions(+), 8 deletions(-)

diff --git a/compiler/basicTypes/RdrName.hs b/compiler/basicTypes/RdrName.hs
index 61ab1a9..bc90daf 100644
--- a/compiler/basicTypes/RdrName.hs
+++ b/compiler/basicTypes/RdrName.hs
@@ -112,7 +112,7 @@ import Data.List( sortBy, foldl', nub )
 --           'ApiAnnotation.AnnOpen'  @'('@ or @'['@ or @'[:'@,
 --           'ApiAnnotation.AnnClose' @')'@ or @']'@ or @':]'@,,
 --           'ApiAnnotation.AnnBackquote' @'`'@,
---           'ApiAnnotation.AnnVal','ApiAnnotation.AnnTildehsh',
+--           'ApiAnnotation.AnnVal'
 --           'ApiAnnotation.AnnTilde',
 
 -- For details on above see note [Api annotations] in ApiAnnotation
diff --git a/compiler/parser/ApiAnnotation.hs b/compiler/parser/ApiAnnotation.hs
index 282d390..4d1758f 100644
--- a/compiler/parser/ApiAnnotation.hs
+++ b/compiler/parser/ApiAnnotation.hs
@@ -280,7 +280,6 @@ data AnnKeywordId
     | AnnThIdTySplice -- ^ '$$'
     | AnnThTyQuote -- ^ double '''
     | AnnTilde -- ^ '~'
-    | AnnTildehsh -- ^ '~#'
     | AnnType
     | AnnUnit -- ^ '()' for types
     | AnnUsing
@@ -322,7 +321,7 @@ instance Outputable AnnotationComment where
 
 -- | - 'ApiAnnotation.AnnKeywordId' : 'ApiAnnotation.AnnOpen',
 --             'ApiAnnotation.AnnClose','ApiAnnotation.AnnComma',
---             'ApiAnnotation.AnnRarrow','ApiAnnotation.AnnTildehsh',
+--             'ApiAnnotation.AnnRarrow'
 --             'ApiAnnotation.AnnTilde'
 --   - May have 'ApiAnnotation.AnnComma' when in a list
 type LRdrName = Located RdrName
diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x
index fc8b988..006facc 100644
--- a/compiler/parser/Lexer.x
+++ b/compiler/parser/Lexer.x
@@ -678,7 +678,6 @@ data Token
   | ITrarrow            IsUnicodeSyntax
   | ITat
   | ITtilde
-  | ITtildehsh
   | ITdarrow            IsUnicodeSyntax
   | ITminus
   | ITbang
@@ -888,7 +887,6 @@ reservedSymsFM = listToUFM $
        ,("->",  ITrarrow NormalSyntax, always)
        ,("@",   ITat,                  always)
        ,("~",   ITtilde,               always)
-       ,("~#",  ITtildehsh,            magicHashEnabled)
        ,("=>",  ITdarrow NormalSyntax, always)
        ,("-",   ITminus,               always)
        ,("!",   ITbang,                always)
diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y
index 533e21d..af8c95f 100644
--- a/compiler/parser/Parser.y
+++ b/compiler/parser/Parser.y
@@ -522,7 +522,6 @@ are the most common patterns, rewritten as regular expressions for clarity:
  '->'           { L _ (ITrarrow _) }
  '@'            { L _ ITat }
  '~'            { L _ ITtilde }
- '~#'           { L _ ITtildehsh }
  '=>'           { L _ (ITdarrow _) }
  '-'            { L _ ITminus }
  '!'            { L _ ITbang }
@@ -3119,8 +3118,6 @@ ntgtycon :: { Located RdrName }  -- A "general" qualified tycon, excluding unit
         | '(' '->' ')'          {% ams (sLL $1 $> $ getRdrName funTyCon)
                                        [mop $1,mu AnnRarrow $2,mcp $3] }
         | '[' ']'               {% ams (sLL $1 $> $ listTyCon_RDR) [mos $1,mcs $2] }
-        | '(' '~#' ')'          {% ams (sLL $1 $> $ getRdrName eqPrimTyCon)
-                                        [mop $1,mj AnnTildehsh $2,mcp $3] }
 
 oqtycon :: { Located RdrName }  -- An "ordinary" qualified tycon;
                                 -- These can appear in export lists



More information about the ghc-commits mailing list