[Git][ghc/ghc][master] Consolidate imports in getMinimalImports (#18264)

Marge Bot gitlab at gitlab.haskell.org
Thu Aug 27 18:19:31 UTC 2020



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
01ff8c89 by Aditya Gupta at 2020-08-27T14:19:26-04:00
Consolidate imports in getMinimalImports (#18264)

- - - - -


5 changed files:

- compiler/GHC/Rename/Names.hs
- testsuite/tests/rename/should_compile/Makefile
- + testsuite/tests/rename/should_compile/T18264.hs
- + testsuite/tests/rename/should_compile/T18264.stdout
- testsuite/tests/rename/should_compile/all.T


Changes:

=====================================
compiler/GHC/Rename/Names.hs
=====================================
@@ -4,7 +4,7 @@
 Extracting imported and top-level names in scope
 -}
 
-{-# LANGUAGE CPP, NondecreasingIndentation, MultiWayIf, NamedFieldPuns #-}
+{-# LANGUAGE CPP, NondecreasingIndentation #-}
 {-# LANGUAGE FlexibleContexts #-}
 {-# LANGUAGE RankNTypes #-}
 {-# LANGUAGE ScopedTypeVariables #-}
@@ -72,7 +72,7 @@ import Data.Either      ( partitionEithers, isRight, rights )
 import Data.Map         ( Map )
 import qualified Data.Map as Map
 import Data.Ord         ( comparing )
-import Data.List        ( partition, (\\), find, sortBy )
+import Data.List        ( partition, (\\), find, sortBy, groupBy, sortOn )
 import Data.Function    ( on )
 import qualified Data.Set as S
 import System.FilePath  ((</>))
@@ -1570,7 +1570,7 @@ decls, and simply trim their import lists.  NB that
 -}
 
 getMinimalImports :: [ImportDeclUsage] -> RnM [LImportDecl GhcRn]
-getMinimalImports = mapM mk_minimal
+getMinimalImports = fmap combine . mapM mk_minimal
   where
     mk_minimal (L l decl, used_gres, unused)
       | null unused
@@ -1623,6 +1623,25 @@ getMinimalImports = mapM mk_minimal
 
           all_non_overloaded = all (not . flIsOverloaded)
 
+    combine :: [LImportDecl GhcRn] -> [LImportDecl GhcRn]
+    combine = map merge . groupBy ((==) `on` getKey) . sortOn getKey
+
+    getKey :: LImportDecl GhcRn -> (Bool, Maybe ModuleName, ModuleName)
+    getKey decl =
+      ( isImportDeclQualified . ideclQualified $ idecl -- is this qualified? (important that this be first)
+      , unLoc <$> ideclAs idecl -- what is the qualifier (inside Maybe monad)
+      , unLoc . ideclName $ idecl -- Module Name
+      )
+      where
+        idecl :: ImportDecl GhcRn
+        idecl = unLoc decl
+
+    merge :: [LImportDecl GhcRn] -> LImportDecl GhcRn
+    merge []                     = error "getMinimalImports: unexpected empty list"
+    merge decls@((L l decl) : _) = L l (decl { ideclHiding = Just (False, L l lies) })
+      where lies = concatMap (unLoc . snd) $ mapMaybe (ideclHiding . unLoc) decls
+
+
 printMinimalImports :: HscSource -> [ImportDeclUsage] -> RnM ()
 -- See Note [Printing minimal imports]
 printMinimalImports hsc_src imports_w_usage


=====================================
testsuite/tests/rename/should_compile/Makefile
=====================================
@@ -60,3 +60,8 @@ T7969:
 T18497:
 	'$(TEST_HC)' $(TEST_HC_OPTS) -fno-code T18497_Foo.hs T18497_Bar.hs -ddump-minimal-imports
 	cat T18497_Bar.imports-boot
+
+T18264:
+	$(RM) T18264.hi T18264.o T18264.imports
+	'$(TEST_HC)' $(TEST_HC_OPTS) -ddump-minimal-imports -c T18264.hs
+	cat T18264.imports


=====================================
testsuite/tests/rename/should_compile/T18264.hs
=====================================
@@ -0,0 +1,20 @@
+module T18264 where
+
+import Data.Char (isDigit)
+import Data.Maybe (isJust)
+import Data.Char (isPrint)
+import Data.List (sortOn)
+import Data.Char (isLetter)
+import Data.Maybe hiding (isNothing)
+
+import qualified Data.List as S (sort)
+import qualified Data.Char as C --only isDigit & isLetter used later
+import qualified Data.List as T (nub)
+
+test1 x = isDigit x || isLetter x
+test2a = isJust
+test2b = fromJust
+test3 x = C.isDigit x || C.isLetter x
+test4 xs = S.sort xs
+test5 xs = T.nub xs
+test6 f xs = sortOn f xs


=====================================
testsuite/tests/rename/should_compile/T18264.stdout
=====================================
@@ -0,0 +1,6 @@
+import Data.Char ( isDigit, isLetter )
+import Data.List ( sortOn )
+import Data.Maybe ( fromJust, isJust )
+import qualified Data.Char as C ( isLetter, isDigit )
+import qualified Data.List as S ( sort )
+import qualified Data.List as T ( nub )


=====================================
testsuite/tests/rename/should_compile/all.T
=====================================
@@ -175,3 +175,4 @@ test('T17244C', normal, compile, [''])
 test('T17832', [], multimod_compile, ['T17832M1', 'T17832M2'])
 test('T17837', normal, compile, [''])
 test('T18497', [], makefile_test, ['T18497'])
+test('T18264', [], makefile_test, ['T18264'])



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

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/01ff8c89727a91cbc1571ae54f73f5919d6aaa71
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/20200827/aaa8db90/attachment-0001.html>


More information about the ghc-commits mailing list