[Git][ghc/ghc][wip/T18302] WIP on #18302

Krzysztof Gogolewski gitlab at gitlab.haskell.org
Sun Sep 13 12:01:30 UTC 2020



Krzysztof Gogolewski pushed to branch wip/T18302 at Glasgow Haskell Compiler / GHC


Commits:
379e4de0 by Krzysztof Gogolewski at 2020-09-13T14:01:07+02:00
WIP on #18302

Culprit:

pickGREsModExp :: ModuleName -> [GlobalRdrElt] -> [(GlobalRdrElt,GlobalRdrElt)]
-- ^ Pick GREs that are in scope *both* qualified *and* unqualified
-- Return each GRE that is, as a pair
--    (qual_gre, unqual_gre)
-- These two GREs are the original GRE with imports filtered to express how
-- it is in scope qualified an unqualified respectively
--
-- Used only for the 'module M' item in export list;
--   see 'GHC.Tc.Gen.Export.exports_from_avail'
pickGREsModExp mod gres = mapMaybe (pickBothGRE mod) gres

pickBothGRE :: ModuleName -> GlobalRdrElt -> Maybe (GlobalRdrElt, GlobalRdrElt)
pickBothGRE mod gre@(GRE { gre_name = n })
  | isBuiltInSyntax n                = Nothing
  | Just gre1 <- pickQualGRE mod gre
  , Just gre2 <- pickUnqualGRE   gre = Just (gre1, gre2)
  | otherwise                        = Nothing
  where
        -- isBuiltInSyntax filter out names for built-in syntax They
        -- just clutter up the environment (esp tuples), and the
        -- parser will generate Exact RdrNames for them, so the
        -- cluttered envt is no use.  Really, it's only useful for
        -- GHC.Base and GHC.Tuple.

- - - - -


5 changed files:

- compiler/GHC/Builtin/Types/Prim.hs
- libraries/base/Data/Typeable/Internal.hs
- libraries/base/GHC/Exception.hs
- libraries/base/GHC/Exts.hs
- libraries/base/Unsafe/Coerce.hs


Changes:

=====================================
compiler/GHC/Builtin/Types/Prim.hs
=====================================
@@ -11,8 +11,6 @@ Wired-in knowledge about primitive types
 -- | This module defines TyCons that can't be expressed in Haskell.
 --   They are all, therefore, wired-in TyCons.  C.f module "GHC.Builtin.Types"
 module GHC.Builtin.Types.Prim(
-        mkPrimTyConName, -- For implicit parameters in GHC.Builtin.Types only
-
         mkTemplateKindVars, mkTemplateTyVars, mkTemplateTyVarsFrom,
         mkTemplateKiTyVars, mkTemplateKiTyVar,
 
@@ -402,7 +400,7 @@ multiplicityTyVar = mkTemplateTyVars (repeat multiplicityTy) !! 13  -- selects '
 -}
 
 funTyConName :: Name
-funTyConName = mkPrimTyConName (fsLit "FUN") funTyConKey funTyCon
+funTyConName = mkPrimTcName UserSyntax (fsLit "FUN") funTyConKey funTyCon
 
 -- | The @FUN@ type constructor.
 --
@@ -536,12 +534,7 @@ tYPETyCon = mkKindTyCon tYPETyConName
 
 -- If you edit these, you may need to update the GHC formalism
 -- See Note [GHC Formalism] in GHC.Core.Lint
-tYPETyConName             = mkPrimTyConName (fsLit "TYPE") tYPETyConKey tYPETyCon
-
-mkPrimTyConName :: FastString -> Unique -> TyCon -> Name
-mkPrimTyConName = mkPrimTcName BuiltInSyntax
-  -- All of the super kinds and kinds are defined in Prim,
-  -- and use BuiltInSyntax, because they are never in scope in the source
+tYPETyConName             = mkPrimTcName UserSyntax (fsLit "TYPE") tYPETyConKey tYPETyCon
 
 mkPrimTcName :: BuiltInSyntax -> FastString -> Unique -> TyCon -> Name
 mkPrimTcName built_in_syntax occ key tycon


=====================================
libraries/base/Data/Typeable/Internal.hs
=====================================
@@ -82,10 +82,9 @@ module Data.Typeable.Internal (
     typeSymbolTypeRep, typeNatTypeRep,
   ) where
 
-import GHC.Prim ( FUN )
 import GHC.Base
 import qualified GHC.Arr as A
-import GHC.Types ( TYPE, Multiplicity (Many) )
+import GHC.Types ( Multiplicity (Many) )
 import Data.Type.Equality
 import GHC.List ( splitAt, foldl', elem )
 import GHC.Word


=====================================
libraries/base/GHC/Exception.hs
=====================================
@@ -38,7 +38,6 @@ import GHC.Base
 import GHC.Show
 import GHC.Stack.Types
 import GHC.OldList
-import GHC.Prim
 import GHC.IO.Unsafe
 import {-# SOURCE #-} GHC.Stack.CCS
 import GHC.Exception.Type


=====================================
libraries/base/GHC/Exts.hs
=====================================
@@ -34,7 +34,6 @@ module GHC.Exts
         maxTupleSize,
 
         -- * Primitive operations
-        FUN, -- See https://gitlab.haskell.org/ghc/ghc/issues/18302
         module GHC.Prim,
         module GHC.Prim.Ext,
         shiftL#, shiftRL#, iShiftL#, iShiftRA#, iShiftRL#,
@@ -91,7 +90,7 @@ module GHC.Exts
         type (~~),
 
         -- * Representation polymorphism
-        GHC.Prim.TYPE, RuntimeRep(..), VecCount(..), VecElem(..),
+        RuntimeRep(..), VecCount(..), VecElem(..),
 
         -- * Transform comprehensions
         Down(..), groupWith, sortWith, the,


=====================================
libraries/base/Unsafe/Coerce.hs
=====================================
@@ -24,8 +24,6 @@ import GHC.Arr (amap) -- For amap/unsafeCoerce rule
 import GHC.Base
 import GHC.Num.Integer () -- See Note [Depend on GHC.Num.Integer] in GHC.Base
 
-import GHC.Types
-
 {- Note [Implementing unsafeCoerce]
 ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
 The implementation of unsafeCoerce is surprisingly subtle.



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/379e4de0d59b88c3d3fcae3bc26c4f32a9e51c73
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/20200913/66bc10bb/attachment-0001.html>


More information about the ghc-commits mailing list