[Git][ghc/ghc][wip/T18126] Fix HIE-processing for HsUnboundVar

Simon Peyton Jones gitlab at gitlab.haskell.org
Thu Aug 13 09:39:32 UTC 2020



Simon Peyton Jones pushed to branch wip/T18126 at Glasgow Haskell Compiler / GHC


Commits:
53904905 by Simon Peyton Jones at 2020-08-13T10:38:51+01:00
Fix HIE-processing for HsUnboundVar

- - - - -


1 changed file:

- compiler/GHC/Iface/Ext/Ast.hs


Changes:

=====================================
compiler/GHC/Iface/Ext/Ast.hs
=====================================
@@ -785,6 +785,7 @@ class ( IsPass p
       , Data (HsTupArg (GhcPass p))
       , Data (IPBind (GhcPass p))
       , ToHie (Context (Located (IdGhcP p)))
+      , ToHie (Context (Located (XUnboundVar (GhcPass p))))
       , ToHie (RFContext (Located (AmbiguousFieldOcc (GhcPass p))))
       , ToHie (RFContext (Located (FieldOcc (GhcPass p))))
       , ToHie (TScoped (LHsWcType (GhcPass (NoGhcTcPass p))))
@@ -799,6 +800,9 @@ instance HiePass 'Renamed where
 instance HiePass 'Typechecked where
   hiePass = HieTc
 
+instance ToHie (Context (Located NoExtField)) where
+  toHie _ = pure []
+
 instance HiePass p => ToHie (BindContext (Located (HsBind (GhcPass p)))) where
   toHie (BC context scope b@(L span bind)) =
     concatM $ getTypeNode b : case bind of
@@ -1042,8 +1046,8 @@ instance HiePass p => ToHie (Located (HsExpr (GhcPass p))) where
         [ toHie $ C Use (L mspan var)
              -- Patch up var location since typechecker removes it
         ]
-      HsUnboundVar _ _ ->
-        []
+      HsUnboundVar var _ ->
+        [ toHie $ C Use (L mspan var) ]
       HsConLikeOut _ con ->
         [ toHie $ C Use $ L mspan $ conLikeName con
         ]



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/53904905fc1bf26a1834f344bbd52eeb9be6937f
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/20200813/92338fbc/attachment-0001.html>


More information about the ghc-commits mailing list