1
1
mirror of https://github.com/tweag/ormolu.git synced 2024-09-11 13:16:13 +03:00

Put "this" PackageImports at the end

This commit is contained in:
Alexander Esgen 2023-08-17 19:22:08 +02:00 committed by Mark Karpov
parent 8c85629fd9
commit f94567aa2d
4 changed files with 28 additions and 5 deletions

View File

@ -12,6 +12,9 @@
* Update `displayException` for `OrmoluException` to pretty print the
exception. [PR 1031](https://github.com/tweag/ormolu/pull/1031).
* Put `"this"` `PackageImports` at the end. [Issue
1048](https://github.com/tweag/ormolu/issues/1048).
* Ormolu is now aware of more common module re-exports by default.
* Support explicit mention of target package name in module re-exports. Even

View File

@ -5,3 +5,5 @@ import "a" Ab
import "b" Aa
import "b" Bb
import "c" Ba
import "zzzz" Z
import "this" Y

View File

@ -5,3 +5,6 @@ import "a" Ab
import "c" Ba
import D
import "b" Bb
import "this" Y
import "zzzz" Z

View File

@ -2,6 +2,7 @@
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ViewPatterns #-}
-- | Manipulations on import lists.
module Ormolu.Imports
@ -63,7 +64,7 @@ combineImports (L lx ImportDecl {..}) (L _ y) =
-- the same 'ImportId' they can be merged.
data ImportId = ImportId
{ importIsPrelude :: Bool,
importPkgQual :: Maybe LexicalFastString,
importPkgQual :: ImportPkgQual,
importIdName :: ModuleName,
importSource :: IsBootInterface,
importSafe :: Bool,
@ -73,6 +74,23 @@ data ImportId = ImportId
}
deriving (Eq, Ord)
data ImportPkgQual
= -- | The import is not qualified by a package name.
NoImportPkgQual
| -- | The import is qualified by an external package name.
ImportPkgQual LexicalFastString
| -- | The import is qualified by the current package being built, using the
-- special @this@ package name.
ImportPkgQualThis
deriving stock (Eq, Ord)
mkImportPkgQual :: RawPkgQual -> ImportPkgQual
mkImportPkgQual = \case
NoRawPkgQual -> NoImportPkgQual
RawPkgQual (sl_fs -> fs)
| fs == mkFastString "this" -> ImportPkgQualThis
| otherwise -> ImportPkgQual (LexicalFastString fs)
-- | 'ImportListInterpretation' does not have an 'Ord' instance.
newtype ImportListInterpretationOrd = ImportListInterpretationOrd
{ unImportListInterpretationOrd :: ImportListInterpretation
@ -91,7 +109,7 @@ importId (L _ ImportDecl {..}) =
ImportId
{ importIsPrelude = isPrelude,
importIdName = moduleName,
importPkgQual = rawPkgQualToLFS ideclPkgQual,
importPkgQual = mkImportPkgQual ideclPkgQual,
importSource = ideclSource,
importSafe = ideclSafe,
importQualified = case ideclQualified of
@ -104,9 +122,6 @@ importId (L _ ImportDecl {..}) =
where
isPrelude = moduleNameString moduleName == "Prelude"
moduleName = unLoc ideclName
rawPkgQualToLFS = \case
RawPkgQual fs -> Just . LexicalFastString . sl_fs $ fs
NoRawPkgQual -> Nothing
-- | Normalize a collection of import\/export items.
normalizeLies :: [LIE GhcPs] -> [LIE GhcPs]