Implement merging on imports

This commit is contained in:
Mark Karpov 2020-06-22 12:25:59 +02:00
parent 03e6c70a78
commit ca83f15869
16 changed files with 101 additions and 38 deletions

View File

@ -3,6 +3,9 @@
* Imports in a import lists are now normalized: duplicate imports are
combined/eliminated intelligently.
* Import declarations that can be merged are now automatically merged.
[Issue 414](https://github.com/tweag/ormolu/issues/414).
* The magic comments for disabling and enabling Ormolu now can encompass any
fragment of code provided that the remaining code after exclusion of the
disabled part is still syntactically correct. [Issue

View File

@ -0,0 +1,3 @@
import Foo
import Foo (bar, foo)
import Foo as F

View File

@ -0,0 +1,4 @@
import Foo
import Foo (foo)
import Foo (bar)
import Foo as F

View File

@ -0,0 +1,2 @@
import "bar" Foo (bar)
import "foo" Foo (baz, foo)

View File

@ -0,0 +1,3 @@
import "foo" Foo (foo)
import "bar" Foo (bar)
import "foo" Foo (baz)

View File

@ -0,0 +1,2 @@
import Foo hiding (bar4, foo2)
import qualified Foo (bar3, foo1)

View File

@ -0,0 +1,4 @@
import qualified Foo (foo1)
import Foo hiding (foo2)
import qualified Foo (bar3)
import Foo hiding (bar4)

View File

@ -1,5 +1,5 @@
{-# LANGUAGE ImportQualifiedPost #-}
import Data.Text qualified as T
import Data.Text qualified (a, b, c)
import Data.Text qualified hiding (a, b, c)
import Data.Text qualified as T

View File

@ -1,4 +1,4 @@
module P where
import qualified Prelude
import Prelude hiding (id, (.))
import qualified Prelude

View File

@ -1,8 +1,5 @@
import Data.Text
import Data.Text
import qualified Data.Text as T
import Data.Text (a, b, c)
import Data.Text hiding (a, b, c)
import qualified Data.Text (a, b, c)
import Data.Text (a, b, c)
import Data.Text hiding (a, b, c)
import Data.Text (a, b, c)
import Data.Text hiding (a, b, c)
import qualified Data.Text as T

View File

@ -1,5 +1,5 @@
Formatting is not idempotent:
src/IDE/Pane/Modules.hs<rendered>:1189:7
src/IDE/Pane/Modules.hs<rendered>:1184:7
before: "cr\n -- show"
after: "cr\n in -- show"
Please, consider reporting the bug.

View File

@ -14,7 +14,7 @@ import Data.Text (Text)
import qualified Data.Text as T
import qualified FastString as GHC
import GHC
import Ormolu.Imports (sortImports)
import Ormolu.Imports (normalizeImports)
import Ormolu.Parser.CommentStream
import Ormolu.Parser.Result
import Ormolu.Utils
@ -47,8 +47,8 @@ diffParseResult
} =
matchIgnoringSrcSpans cstream0 cstream1
<> matchIgnoringSrcSpans
hs0 {hsmodImports = sortImports (hsmodImports hs0)}
hs1 {hsmodImports = sortImports (hsmodImports hs1)}
hs0 {hsmodImports = normalizeImports (hsmodImports hs0)}
hs1 {hsmodImports = normalizeImports (hsmodImports hs1)}
-- | Compare two values for equality disregarding differences in 'SrcSpan's
-- and the ordering of import lists.

View File

@ -4,48 +4,94 @@
-- | Manipulations on import lists.
module Ormolu.Imports
( sortImports,
( normalizeImports,
)
where
import Data.Bifunctor
import Data.Char (isAlphaNum)
import Data.Function (on)
import Data.Generics (gcompare)
import Data.List (foldl', nubBy, sortBy, sortOn)
import Data.Map.Strict (Map)
import qualified Data.Map.Strict as M
import FastString (FastString)
import GHC hiding (GhcPs, IE)
import GHC.Hs.Extension
import GHC.Hs.ImpExp (IE (..))
import Ormolu.Utils (notImplemented, showOutputable)
-- | Sort imports by module name. This also sorts and normalizes explicit
-- import lists for each declaration.
sortImports :: [LImportDecl GhcPs] -> [LImportDecl GhcPs]
sortImports = sortBy compareIdecl . fmap (fmap sortImportLists)
-- | Sort and normalize imports.
normalizeImports :: [LImportDecl GhcPs] -> [LImportDecl GhcPs]
normalizeImports =
fmap snd
. M.toAscList
. M.fromListWith combineImports
. fmap (\x -> (importId x, g x))
where
sortImportLists :: ImportDecl GhcPs -> ImportDecl GhcPs
sortImportLists = \case
ImportDecl {..} ->
g (L l ImportDecl {..}) =
L
l
ImportDecl
{ ideclHiding = second (fmap normalizeLies) <$> ideclHiding,
..
}
XImportDecl x -> noExtCon x
g _ = notImplemented "XImportDecl"
-- | Compare two @'LImportDecl' 'GhcPs'@ things.
compareIdecl :: LImportDecl GhcPs -> LImportDecl GhcPs -> Ordering
compareIdecl (L _ m0) (L _ m1) =
case (isPrelude n0, isPrelude n1) of
(False, False) -> n0 `compare` n1
(True, False) -> GT
(False, True) -> LT
(True, True) -> m0 `gcompare` m1
-- | Combine two import declarations. It should be assumed that 'ImportId's
-- are equal.
combineImports ::
LImportDecl GhcPs ->
LImportDecl GhcPs ->
LImportDecl GhcPs
combineImports (L lx ImportDecl {..}) (L _ y) =
L
lx
ImportDecl
{ ideclHiding = case (ideclHiding, GHC.ideclHiding y) of
(Just (hiding, L l' xs), Just (_, L _ ys)) ->
Just (hiding, (L l' (normalizeLies (xs ++ ys))))
_ -> Nothing,
..
}
combineImports _ _ = notImplemented "XImportDecl"
-- | Import id, a collection of all things that justify having a separate
-- import entry. This is used for merging of imports. If two imports have
-- the same 'ImportId' they can be merged.
data ImportId = ImportId
{ importIsPrelude :: Bool,
importIdName :: ModuleName,
importPkgQual :: Maybe FastString,
importSource :: Bool,
importSafe :: Bool,
importQualified :: Bool,
importImplicit :: Bool,
importAs :: Maybe ModuleName,
importHiding :: Maybe Bool
}
deriving (Eq, Ord)
-- | Obtain an 'ImportId' for a given import.
importId :: LImportDecl GhcPs -> ImportId
importId (L _ ImportDecl {..}) =
ImportId
{ importIsPrelude = isPrelude,
importIdName = moduleName,
importPkgQual = sl_fs <$> ideclPkgQual,
importSource = ideclSource,
importSafe = ideclSafe,
importQualified = case ideclQualified of
QualifiedPre -> True
QualifiedPost -> True
NotQualified -> False,
importImplicit = ideclImplicit,
importAs = unLoc <$> ideclAs,
importHiding = fst <$> ideclHiding
}
where
n0 = unLoc (ideclName m0)
n1 = unLoc (ideclName m1)
isPrelude = (== "Prelude") . moduleNameString
isPrelude = moduleNameString moduleName == "Prelude"
moduleName = unLoc ideclName
importId _ = notImplemented "XImportDecl"
-- | Normalize a collection of import\/export items.
normalizeLies :: [LIE GhcPs] -> [LIE GhcPs]

View File

@ -11,7 +11,7 @@ where
import Control.Monad
import qualified Data.Text as T
import GHC
import Ormolu.Imports
import Ormolu.Imports (normalizeImports)
import Ormolu.Parser.CommentStream
import Ormolu.Parser.Pragma
import Ormolu.Parser.Shebang
@ -69,7 +69,7 @@ p_hsModule mstackHeader shebangs pragmas qualifiedPost HsModule {..} = do
txt "where"
newline
newline
forM_ (sortImports hsmodImports) (located' (p_hsmodImport qualifiedPost))
forM_ (normalizeImports hsmodImports) (located' (p_hsmodImport qualifiedPost))
newline
switchLayout (getLoc <$> hsmodDecls) $ do
p_hsDecls Free hsmodDecls

View File

@ -11,8 +11,7 @@ where
import Control.Monad
import Data.Char (isSpace)
import qualified Data.List as L
import Data.Maybe (isJust)
import Data.Maybe (maybeToList)
import Data.Maybe (isJust, maybeToList)
import FastString
import Ormolu.Config (RegionDeltas (..))
import Ormolu.Parser.Shebang (isShebang)

View File

@ -22,8 +22,8 @@ where
import Data.Char (isSpace)
import Data.List (dropWhileEnd)
import qualified Data.List.NonEmpty as NE
import Data.List.NonEmpty (NonEmpty (..))
import qualified Data.List.NonEmpty as NE
import Data.Maybe (fromMaybe)
import Data.Text (Text)
import qualified Data.Text as T