[Git][ghc/ghc][wip/T18599] Some reformatting and tests

Shayne Fletcher gitlab at gitlab.haskell.org
Wed Sep 9 14:31:24 UTC 2020



Shayne Fletcher pushed to branch wip/T18599 at Glasgow Haskell Compiler / GHC


Commits:
42011e7d by Shayne Fletcher at 2020-09-09T10:30:53-04:00
Some reformatting and tests

- - - - -


4 changed files:

- compiler/GHC/Parser.y
- compiler/GHC/Parser/PostProcess.hs
- + record-dot-syntax-tests/Construction.hs
- + record-dot-syntax-tests/Pattern.hs


Changes:

=====================================
compiler/GHC/Parser.y
=====================================
@@ -3239,7 +3239,7 @@ fbinds1 :: { forall b. DisambECP b => PV ([AddAnn],([Fbind b], Maybe SrcSpan)) }
 
 fbind   :: { forall b. DisambECP b => PV (Fbind b) }
         : qvar '=' texp  { unECP $3 >>= \ $3 ->
-                           return $ Fbind (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False)
+                           fmap Fbind $ return (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False)
                             -- ams (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) $3 False) [mj AnnEqual $2]
                           }
                         -- RHS is a 'texp', allowing view patterns (#6038)
@@ -3247,32 +3247,32 @@ fbind   :: { forall b. DisambECP b => PV (Fbind b) }
                         -- f (R { x = show -> s }) = ...
 
         | qvar          { placeHolderPunRhs >>= \rhs ->
-                          return $ Fbind (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) rhs True)
+                          fmap Fbind $ return (sLL $1 $> $ HsRecField (sL1 $1 $ mkFieldOcc $1) rhs True)
                         }
                         -- In the punning case, use a place-holder
                         -- The renamer fills in the final value
 
         -- See Note [Whitespace-sensitive operator parsing] in Lexer.x
         | field TIGHT_INFIX_PROJ fieldToUpdate '=' texp
-           {do
-              $5 <- unECP $5
-              fmap Pbind $ mkHsFieldUpdaterPV (comb2 $1 $5) ($1 : reverse $3) $5
-           }
+                        { do
+                            $5 <- unECP $5
+                            fmap Pbind $ mkHsFieldUpdaterPV (comb2 $1 $5) ($1 : reverse $3) $5
+                        }
 
         -- See Note [Whitespace-sensitive operator parsing] in Lexer.x
         | field TIGHT_INFIX_PROJ fieldToUpdate
-           {do
-              let top = $1
-                  fields = top : reverse $3
-                  final = last fields
-                  l = comb2 top final
-              puns <- getBit RecordPunsBit
-              when (not puns) $
-                addError l $
-                  text "For this to work, enable NamedFieldPuns."
-              var <- mkHsVarPV (noLoc (mkRdrUnqual . mkVarOcc . unpackFS . unLoc $ final))
-              fmap Pbind $ mkHsFieldUpdaterPV l fields var
-           }
+                        { do
+                            let top = $1
+                                fields = top : reverse $3
+                                final = last fields
+                                l = comb2 top final
+                            puns <- getBit RecordPunsBit
+                            when (not puns) $
+                              addError l $
+                                text "For this to work, enable NamedFieldPuns."
+                            var <- mkHsVarPV (noLoc (mkRdrUnqual . mkVarOcc . unpackFS . unLoc $ final))
+                            fmap Pbind $ mkHsFieldUpdaterPV l fields var
+                        }
 
 fieldToUpdate :: { [Located FastString] }
 fieldToUpdate


=====================================
compiler/GHC/Parser/PostProcess.hs
=====================================
@@ -1523,7 +1523,7 @@ instance DisambECP (HsCmd GhcPs) where
   ecpFromExp' (L l e) = cmdFail l (ppr e)
   mkHsFieldUpdaterPV l _ _ =
     cmdFail l $
-    text "Field update syntax is not supported in commands."
+    text "Field selector syntax is not supported in commands."
   mkHsLamPV l mg = return $ L l (HsCmdLam noExtField mg)
   mkHsLetPV l bs e = return $ L l (HsCmdLet noExtField bs e)
   type InfixOp (HsCmd GhcPs) = HsExpr GhcPs
@@ -1677,7 +1677,7 @@ instance DisambECP (PatBuilder GhcPs) where
       text "Expression syntax in pattern:" <+> ppr e
   mkHsFieldUpdaterPV l _ _ =
     addFatalError l $
-    text "Field update syntax is not supported in patterns."
+    text "Field selector syntax is not supported in patterns."
   mkHsLamPV l _ = addFatalError l $
     text "Lambda-syntax in pattern." $$
     text "Pattern matching on functions is not possible."


=====================================
record-dot-syntax-tests/Construction.hs
=====================================
@@ -0,0 +1,4 @@
+{-# LANGUAGE RecordDotSyntax #-}
+
+no = Foo { bar.baz = 1 }
+  -- Syntax error: Can't use '.' in construction.


=====================================
record-dot-syntax-tests/Pattern.hs
=====================================
@@ -0,0 +1,5 @@
+{-# LANGUAGE RecordDotSyntax #-}
+
+no Foo{bar.baz = x} = undefined
+  -- Syntax error: "Field selector syntax is not supported in
+  -- patterns."



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/42011e7dac076856d9caf925358d7ab387104de5
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/20200909/5367a748/attachment-0001.html>


More information about the ghc-commits mailing list