[Git][ghc/ghc][wip/tycl-group] 2 commits: improve tcLookupTcTyCon panic message

Vladislav Zavialov gitlab at gitlab.haskell.org
Thu Mar 19 08:12:05 UTC 2020



Vladislav Zavialov pushed to branch wip/tycl-group at Glasgow Haskell Compiler / GHC


Commits:
ffeeea14 by Vladislav Zavialov at 2020-03-19T07:47:56Z
improve tcLookupTcTyCon panic message

- - - - -
5bfed256 by Vladislav Zavialov at 2020-03-19T08:10:45Z
accept new test output

- - - - -


3 changed files:

- compiler/typecheck/TcEnv.hs
- testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
- testsuite/tests/parser/should_compile/T14189.stderr


Changes:

=====================================
compiler/typecheck/TcEnv.hs
=====================================
@@ -464,7 +464,7 @@ tcLookupTcTyCon name = do
     thing <- tcLookup name
     case thing of
         ATcTyCon tc -> return tc
-        _           -> pprPanic "tcLookupTcTyCon" (ppr name)
+        _           -> pprPanic "tcLookupTcTyCon" (ppr name <+> text ":" <+> ppr thing)
 
 getInLocalScope :: TcM (Name -> Bool)
 getInLocalScope = do { lcl_env <- getLclTypeEnv


=====================================
testsuite/tests/parser/should_compile/DumpRenamedAst.stderr
=====================================
@@ -4,7 +4,12 @@
 (Just
  ((,,,)
   (HsGroup
-   (NoExtField)
+   (KindedDecls
+    {NameSet:
+     [{Name: DumpRenamedAst.F1}
+     ,{Name: DumpRenamedAst.Length}
+     ,{Name: DumpRenamedAst.Nat}
+     ,{Name: DumpRenamedAst.Peano}]})
    (XValBindsLR
     (NValBinds
      [((,)
@@ -56,8 +61,7 @@
            []))]})]
      []))
    []
-   [(TyClGroup
-     (NoExtField)
+   [(TcgRn
      [({ DumpRenamedAst.hs:9:1-30 }
        (DataDecl
         (DataDeclRn
@@ -109,10 +113,18 @@
          ({ <no location info> }
           []))))]
      []
-     []
+     [(DeclSigRnCUSK
+       ({ DumpRenamedAst.hs:9:1-30 }
+        (DeclHeaderRn
+         (DataTypeFlavour)
+         ({ DumpRenamedAst.hs:9:6-10 }
+          {Name: DumpRenamedAst.Peano})
+         (HsQTvs
+          []
+          [])
+         (Nothing))))]
      [])
-   ,(TyClGroup
-     (NoExtField)
+   ,(TcgRn
      [({ DumpRenamedAst.hs:11:1-39 }
        (FamDecl
         (NoExtField)
@@ -229,10 +241,37 @@
               {Name: DumpRenamedAst.Peano})))))
          (Nothing))))]
      []
-     []
+     [(DeclSigRnCUSK
+       ({ DumpRenamedAst.hs:11:1-39 }
+        (DeclHeaderRn
+         (ClosedTypeFamilyFlavour)
+         ({ DumpRenamedAst.hs:11:13-18 }
+          {Name: DumpRenamedAst.Length})
+         (HsQTvs
+          [{Name: k}]
+          [({ DumpRenamedAst.hs:11:21-29 }
+            (KindedTyVar
+             (NoExtField)
+             ({ DumpRenamedAst.hs:11:21-22 }
+              {Name: as})
+             ({ DumpRenamedAst.hs:11:27-29 }
+              (HsListTy
+               (NoExtField)
+               ({ DumpRenamedAst.hs:11:28 }
+                (HsTyVar
+                 (NoExtField)
+                 (NotPromoted)
+                 ({ DumpRenamedAst.hs:11:28 }
+                  {Name: k})))))))])
+         (Just
+          ({ DumpRenamedAst.hs:11:35-39 }
+           (HsTyVar
+            (NoExtField)
+            (NotPromoted)
+            ({ DumpRenamedAst.hs:11:35-39 }
+             {Name: DumpRenamedAst.Peano})))))))]
      [])
-   ,(TyClGroup
-     (NoExtField)
+   ,(TcgRn
      [({ DumpRenamedAst.hs:15:1-33 }
        (FamDecl
         (NoExtField)
@@ -274,7 +313,41 @@
                   {Name: GHC.Types.Type})))))))))
          (Nothing))))]
      []
-     []
+     [(DeclSigRnCUSK
+       ({ DumpRenamedAst.hs:15:1-33 }
+        (DeclHeaderRn
+         (DataFamilyFlavour
+          (Nothing))
+         ({ DumpRenamedAst.hs:15:13-15 }
+          {Name: DumpRenamedAst.Nat})
+         (HsQTvs
+          [{Name: k}]
+          [])
+         (Just
+          ({ DumpRenamedAst.hs:15:20-33 }
+           (HsFunTy
+            (NoExtField)
+            ({ DumpRenamedAst.hs:15:20 }
+             (HsTyVar
+              (NoExtField)
+              (NotPromoted)
+              ({ DumpRenamedAst.hs:15:20 }
+               {Name: k})))
+            ({ DumpRenamedAst.hs:15:25-33 }
+             (HsFunTy
+              (NoExtField)
+              ({ DumpRenamedAst.hs:15:25 }
+               (HsTyVar
+                (NoExtField)
+                (NotPromoted)
+                ({ DumpRenamedAst.hs:15:25 }
+                 {Name: k})))
+              ({ DumpRenamedAst.hs:15:30-33 }
+               (HsTyVar
+                (NoExtField)
+                (NotPromoted)
+                ({ DumpRenamedAst.hs:15:30-33 }
+                 {Name: GHC.Types.Type})))))))))))]
      [({ DumpRenamedAst.hs:(18,1)-(19,45) }
        (DataFamInstD
         (NoExtField)
@@ -435,8 +508,7 @@
                (Nothing)))]
             ({ <no location info> }
              [])))))))])
-   ,(TyClGroup
-     (NoExtField)
+   ,(TcgRn
      [({ DumpRenamedAst.hs:21:1-29 }
        (DataDecl
         (DataDeclRn
@@ -506,8 +578,7 @@
      []
      []
      [])
-   ,(TyClGroup
-     (NoExtField)
+   ,(TcgRn
      [({ DumpRenamedAst.hs:23:1-48 }
        (FamDecl
         (NoExtField)
@@ -627,7 +698,52 @@
               {Name: GHC.Types.Type})))))
          (Nothing))))]
      []
-     []
+     [(DeclSigRnCUSK
+       ({ DumpRenamedAst.hs:23:1-48 }
+        (DeclHeaderRn
+         (ClosedTypeFamilyFlavour)
+         ({ DumpRenamedAst.hs:23:13-14 }
+          {Name: DumpRenamedAst.F1})
+         (HsQTvs
+          [{Name: k}]
+          [({ DumpRenamedAst.hs:23:17-22 }
+            (KindedTyVar
+             (NoExtField)
+             ({ DumpRenamedAst.hs:23:17 }
+              {Name: a})
+             ({ DumpRenamedAst.hs:23:22 }
+              (HsTyVar
+               (NoExtField)
+               (NotPromoted)
+               ({ DumpRenamedAst.hs:23:22 }
+                {Name: k})))))
+          ,({ DumpRenamedAst.hs:23:26-39 }
+            (KindedTyVar
+             (NoExtField)
+             ({ DumpRenamedAst.hs:23:26 }
+              {Name: f})
+             ({ DumpRenamedAst.hs:23:31-39 }
+              (HsFunTy
+               (NoExtField)
+               ({ DumpRenamedAst.hs:23:31 }
+                (HsTyVar
+                 (NoExtField)
+                 (NotPromoted)
+                 ({ DumpRenamedAst.hs:23:31 }
+                  {Name: k})))
+               ({ DumpRenamedAst.hs:23:36-39 }
+                (HsTyVar
+                 (NoExtField)
+                 (NotPromoted)
+                 ({ DumpRenamedAst.hs:23:36-39 }
+                  {Name: GHC.Types.Type})))))))])
+         (Just
+          ({ DumpRenamedAst.hs:23:45-48 }
+           (HsTyVar
+            (NoExtField)
+            (NotPromoted)
+            ({ DumpRenamedAst.hs:23:45-48 }
+             {Name: GHC.Types.Type})))))))]
      [])]
    []
    []


=====================================
testsuite/tests/parser/should_compile/T14189.stderr
=====================================
@@ -4,14 +4,15 @@
 (Just
  ((,,,)
   (HsGroup
-   (NoExtField)
+   (KindedDecls
+    {NameSet:
+     []})
    (XValBindsLR
     (NValBinds
      []
      []))
    []
-   [(TyClGroup
-     (NoExtField)
+   [(TcgRn
      [({ T14189.hs:6:1-42 }
        (DataDecl
         (DataDeclRn



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/117800fe7631e454ac7e7db9976c2548bc79f349...5bfed256397ff257023ae2af27c0bc78653905b2

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/compare/117800fe7631e454ac7e7db9976c2548bc79f349...5bfed256397ff257023ae2af27c0bc78653905b2
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/20200319/ad84f48e/attachment-0001.html>


More information about the ghc-commits mailing list