[Git][ghc/ghc][wip/int-index/emb-type] Update the HieVdq test case

Vladislav Zavialov (@int-index) gitlab at gitlab.haskell.org
Thu Jul 20 01:03:00 UTC 2023



Vladislav Zavialov pushed to branch wip/int-index/emb-type at Glasgow Haskell Compiler / GHC


Commits:
f9c86438 by Vladislav Zavialov at 2023-07-20T02:59:51+02:00
Update the HieVdq test case

- - - - -


3 changed files:

- compiler/GHC/Iface/Ext/Ast.hs
- testsuite/tests/hiefile/should_run/HieVdq.hs
- testsuite/tests/hiefile/should_run/HieVdq.stdout


Changes:

=====================================
compiler/GHC/Iface/Ext/Ast.hs
=====================================
@@ -1027,9 +1027,9 @@ instance HiePass p => ToHie (PScoped (LocatedA (Pat (GhcPass p)))) where
                            sig
             HieRn -> pure []
         ]
-      EmbTyPat _ _ _ ->
-         -- TODO (int-index): Return more information? Test case: HieVdq
-        []
+      EmbTyPat _ _ tp ->
+        [ toHie $ TS (ResolvedScopes [scope, pscope]) tp
+        ]
       XPat e ->
         case hiePass @p of
           HieRn -> case e of


=====================================
testsuite/tests/hiefile/should_run/HieVdq.hs
=====================================
@@ -3,16 +3,20 @@
 
 module Main where
 
+import GHC.Types.Name (nameSrcSpan)
 import TestUtils
 import qualified Data.Map as M
 import Data.Foldable
+import Data.Either
 
 f :: forall a -> a -> Maybe a
-f (type t) (x :: t) = Just x
+f (type t) (x :: t) = Just (x :: t)
+--      ^p1      ^p2             ^p3
 
 p1,p2 :: (Int,Int)
-p1 = (11,13)
-p2 = (11,28)
+p1 = (13,9)
+p2 = (13,18)
+p3 = (13,34)
 
 selectPoint' :: HieFile -> (Int,Int) -> HieAST Int
 selectPoint' hf loc =
@@ -20,8 +24,11 @@ selectPoint' hf loc =
 
 main = do
   (df, hf) <- readTestHie "HieVdq.hie"
-  forM_ [p1,p2] $ \point -> do
-    putStr $ "At " ++ show point ++ ", got type: "
-    let types = concatMap nodeType $ getSourcedNodeInfo $ sourcedNodeInfo $ selectPoint' hf point
-    forM_ types $ \typ -> do
-      putStrLn (renderHieType df $ recoverFullType typ (hie_types hf))
+  forM_ [p1,p2,p3] $ \point -> do
+    putStr $ "At " ++ show point ++ ", got names: "
+    let names =
+          concatMap (rights . M.keys . nodeIdentifiers) $
+          M.elems $ getSourcedNodeInfo $
+          sourcedNodeInfo $ selectPoint' hf point
+    forM_ names $ \name -> do
+      putStrLn (render df (nameSrcSpan name, name))


=====================================
testsuite/tests/hiefile/should_run/HieVdq.stdout
=====================================
@@ -1,2 +1,3 @@
-At (11,13), got type: a
-At (11,28), got type: a
+At (13,9), got names: (HieVdq.hs:13:9, t)
+At (13,18), got names: (HieVdq.hs:13:9, t)
+At (13,34), got names: (HieVdq.hs:13:9, t)



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f9c864383ba7afa3f956ea9a17b674a33765ddeb
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/20230719/0585aa55/attachment-0001.html>


More information about the ghc-commits mailing list