[Git][ghc/ghc][wip/ghc-18740-lookup-update] Fall back to types when looking up data constructors (wip)

Danya Rogozin gitlab at gitlab.haskell.org
Thu Sep 24 21:42:13 UTC 2020



Danya Rogozin pushed to branch wip/ghc-18740-lookup-update at Glasgow Haskell Compiler / GHC


Commits:
f03ad0c9 by Daniel Rogozin at 2020-09-25T00:41:34+03:00
Fall back to types when looking up data constructors (wip)

- - - - -


3 changed files:

- compiler/GHC/Rename/Env.hs
- compiler/GHC/Types/Name/Occurrence.hs
- compiler/GHC/Types/Name/Reader.hs


Changes:

=====================================
compiler/GHC/Rename/Env.hs
=====================================
@@ -5,7 +5,7 @@ GHC.Rename.Env contains functions which convert RdrNames into Names.
 
 -}
 
-{-# LANGUAGE CPP, MultiWayIf, NamedFieldPuns #-}
+{-# LANGUAGE CPP, MultiWayIf, NamedFieldPuns, TypeApplications #-}
 
 module GHC.Rename.Env (
         newTopSrcBinder,
@@ -1005,6 +1005,17 @@ lookup_demoted rdr_name
            , text "instead of"
            , quotes (ppr name) <> dot ]
 
+lookup_promoted :: RdrName -> RnM (Maybe Name)
+lookup_promoted rdr_name
+  | Just promoted_rdr <- promoteRdrName rdr_name
+  = do { mb_promoted_rdr <- lookupOccRn_maybe promoted_rdr
+       ; case mb_promoted_rdr of
+           Nothing -> return Nothing
+           Just name -> return (Just name)
+       }
+  | otherwise
+  = return Nothing
+
 badVarInType :: RdrName -> RnM Name
 badVarInType rdr_name
   = do { addErr (text "Illegal promoted term variable in a type:"
@@ -1054,14 +1065,18 @@ lookupOccRn_maybe = lookupOccRnX_maybe lookupGlobalOccRn_maybe id
 
 lookupOccRn_overloaded :: Bool -> RdrName
                        -> RnM (Maybe (Either Name [Name]))
-lookupOccRn_overloaded overload_ok
-  = lookupOccRnX_maybe global_lookup Left
-      where
-        global_lookup :: RdrName -> RnM (Maybe (Either Name [Name]))
-        global_lookup n =
-          runMaybeT . msum . map MaybeT $
-            [ lookupGlobalOccRn_overloaded overload_ok n
-            , fmap Left . listToMaybe <$> lookupQualifiedNameGHCi n ]
+lookupOccRn_overloaded overload_ok rdr_name
+  = do { mb_name <- lookupOccRnX_maybe global_lookup Left rdr_name
+       ; case mb_name of
+           Nothing   -> fmap @Maybe Left <$> lookup_promoted rdr_name
+           p         -> return p }
+
+  where
+    global_lookup :: RdrName -> RnM (Maybe (Either Name [Name]))
+    global_lookup n =
+      runMaybeT . msum . map MaybeT $
+        [ lookupGlobalOccRn_overloaded overload_ok n
+        , fmap Left . listToMaybe <$> lookupQualifiedNameGHCi n ]
 
 
 


=====================================
compiler/GHC/Types/Name/Occurrence.hs
=====================================
@@ -52,6 +52,7 @@ module GHC.Types.Name.Occurrence (
         mkDFunOcc,
         setOccNameSpace,
         demoteOccName,
+        promoteOccName,
         HasOccName(..),
 
         -- ** Derived 'OccName's
@@ -215,6 +216,12 @@ demoteNameSpace DataName = Nothing
 demoteNameSpace TvName = Nothing
 demoteNameSpace TcClsName = Just DataName
 
+promoteNameSpace :: NameSpace -> Maybe NameSpace
+promoteNameSpace DataName = Just TcClsName
+promoteNameSpace VarName = Just TvName
+promoteNameSpace TcClsName = Nothing
+promoteNameSpace TvName = Nothing
+
 {-
 ************************************************************************
 *                                                                      *
@@ -342,6 +349,12 @@ demoteOccName (OccName space name) = do
   space' <- demoteNameSpace space
   return $ OccName space' name
 
+promoteOccName :: OccName -> Maybe OccName
+promoteOccName (OccName space name) = do
+  space' <- promoteNameSpace space
+  return $ OccName space' name
+
+
 -- Name spaces are related if there is a chance to mean the one when one writes
 -- the other, i.e. variables <-> data constructors and type variables <-> type constructors
 nameSpacesRelated :: NameSpace -> NameSpace -> Bool


=====================================
compiler/GHC/Types/Name/Reader.hs
=====================================
@@ -32,7 +32,7 @@ module GHC.Types.Name.Reader (
         nameRdrName, getRdrName,
 
         -- ** Destruction
-        rdrNameOcc, rdrNameSpace, demoteRdrName,
+        rdrNameOcc, rdrNameSpace, demoteRdrName, promoteRdrName,
         isRdrDataCon, isRdrTyVar, isRdrTc, isQual, isQual_maybe, isUnqual,
         isOrig, isOrig_maybe, isExact, isExact_maybe, isSrcRdrName,
 
@@ -186,6 +186,12 @@ demoteRdrName (Qual m occ) = fmap (Qual m) (demoteOccName occ)
 demoteRdrName (Orig _ _) = Nothing
 demoteRdrName (Exact _) = Nothing
 
+promoteRdrName :: RdrName -> Maybe RdrName
+promoteRdrName (Unqual occ) = fmap Unqual (promoteOccName occ)
+promoteRdrName (Qual m occ) = fmap (Qual m) (promoteOccName occ)
+promoteRdrName (Orig m occ) = fmap (Orig m) (promoteOccName occ)
+promoteRdrName (Exact _) = Nothing
+
         -- These two are the basic constructors
 mkRdrUnqual :: OccName -> RdrName
 mkRdrUnqual occ = Unqual occ



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/f03ad0c9b719fec6ab63a151e0dc7b39a49fabf6
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/20200924/23c3267b/attachment-0001.html>


More information about the ghc-commits mailing list