summaryrefslogtreecommitdiff
path: root/compiler
diff options
context:
space:
mode:
Diffstat (limited to 'compiler')
-rw-r--r--compiler/hsSyn/HsImpExp.hs37
-rw-r--r--compiler/main/DynFlags.hs7
-rw-r--r--compiler/main/HeaderInfo.hs2
-rw-r--r--compiler/main/HscStats.hs7
-rw-r--r--compiler/parser/Lexer.x2
-rw-r--r--compiler/parser/Parser.y34
-rw-r--r--compiler/parser/RdrHsSyn.hs50
-rw-r--r--compiler/rename/RnNames.hs8
-rw-r--r--compiler/typecheck/TcRnDriver.hs2
9 files changed, 121 insertions, 28 deletions
diff --git a/compiler/hsSyn/HsImpExp.hs b/compiler/hsSyn/HsImpExp.hs
index d97be4bd54..1d487565e2 100644
--- a/compiler/hsSyn/HsImpExp.hs
+++ b/compiler/hsSyn/HsImpExp.hs
@@ -29,6 +29,7 @@ import SrcLoc
import HsExtension
import Data.Data
+import Data.Maybe
{-
************************************************************************
@@ -48,6 +49,29 @@ type LImportDecl pass = Located (ImportDecl pass)
-- For details on above see note [Api annotations] in ApiAnnotation
+-- | If/how an import is 'qualified'.
+data ImportDeclQualifiedStyle
+ = QualifiedPre -- ^ 'qualified' appears in prepositive position.
+ | QualifiedPost -- ^ 'qualified' appears in postpositive position.
+ | NotQualified -- ^ Not qualified.
+ deriving (Eq, Data)
+
+-- | Given two possible located 'qualified' tokens, compute a style
+-- (in a conforming Haskell program only one of the two can be not
+-- 'Nothing'). This is called from 'Parser.y'.
+importDeclQualifiedStyle :: Maybe (Located a)
+ -> Maybe (Located a)
+ -> ImportDeclQualifiedStyle
+importDeclQualifiedStyle mPre mPost =
+ if isJust mPre then QualifiedPre
+ else if isJust mPost then QualifiedPost else NotQualified
+
+-- | Convenience function to answer the question if an import decl. is
+-- qualified.
+isImportDeclQualified :: ImportDeclQualifiedStyle -> Bool
+isImportDeclQualified NotQualified = False
+isImportDeclQualified _ = True
+
-- | Import Declaration
--
-- A single Haskell @import@ declaration.
@@ -60,7 +84,7 @@ data ImportDecl pass
ideclPkgQual :: Maybe StringLiteral, -- ^ Package qualifier.
ideclSource :: Bool, -- ^ True <=> {-\# SOURCE \#-} import
ideclSafe :: Bool, -- ^ True => safe import
- ideclQualified :: Bool, -- ^ True => qualified
+ ideclQualified :: ImportDeclQualifiedStyle, -- ^ If/how the import is qualified.
ideclImplicit :: Bool, -- ^ True => implicit import (of Prelude)
ideclAs :: Maybe (Located ModuleName), -- ^ as Module
ideclHiding :: Maybe (Bool, Located [LIE pass])
@@ -96,7 +120,7 @@ simpleImportDecl mn = ImportDecl {
ideclSource = False,
ideclSafe = False,
ideclImplicit = False,
- ideclQualified = False,
+ ideclQualified = NotQualified,
ideclAs = Nothing,
ideclHiding = Nothing
}
@@ -109,7 +133,7 @@ instance (p ~ GhcPass pass,OutputableBndrId p)
, ideclQualified = qual, ideclImplicit = implicit
, ideclAs = as, ideclHiding = spec })
= hang (hsep [text "import", ppr_imp from, pp_implicit implicit, pp_safe safe,
- pp_qual qual, pp_pkg pkg, ppr mod', pp_as as])
+ pp_qual qual False, pp_pkg pkg, ppr mod', pp_qual qual True, pp_as as])
4 (pp_spec spec)
where
pp_implicit False = empty
@@ -119,8 +143,11 @@ instance (p ~ GhcPass pass,OutputableBndrId p)
pp_pkg (Just (StringLiteral st p))
= pprWithSourceText st (doubleQuotes (ftext p))
- pp_qual False = empty
- pp_qual True = text "qualified"
+ pp_qual QualifiedPre False = text "qualified" -- Prepositive qualifier/prepositive position.
+ pp_qual QualifiedPost True = text "qualified" -- Postpositive qualifier/postpositive position.
+ pp_qual QualifiedPre True = empty -- Prepositive qualifier/postpositive position.
+ pp_qual QualifiedPost False = empty -- Postpositive qualifier/prepositive position.
+ pp_qual NotQualified _ = empty
pp_safe False = empty
pp_safe True = text "safe"
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 01750a8bd0..1a62d9b15f 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -843,6 +843,7 @@ data WarningFlag =
| Opt_WarnImplicitKindVars -- Since 8.6
| Opt_WarnSpaceAfterBang
| Opt_WarnMissingDerivingStrategies -- Since 8.8
+ | Opt_WarnPrepositiveQualifiedModule -- Since TBD
deriving (Eq, Show, Enum)
data Language = Haskell98 | Haskell2010
@@ -4070,7 +4071,10 @@ wWarningFlagsDeps = [
flagSpec "star-binder" Opt_WarnStarBinder,
flagSpec "star-is-type" Opt_WarnStarIsType,
flagSpec "missing-space-after-bang" Opt_WarnSpaceAfterBang,
- flagSpec "partial-fields" Opt_WarnPartialFields ]
+ flagSpec "partial-fields" Opt_WarnPartialFields,
+ flagSpec "prepositive-qualified-module"
+ Opt_WarnPrepositiveQualifiedModule
+ ]
-- | These @-\<blah\>@ flags can all be reversed with @-no-\<blah\>@
negatableFlagsDeps :: [(Deprecation, FlagSpec GeneralFlag)]
@@ -4396,6 +4400,7 @@ xFlagsDeps = [
setGenDeriving,
flagSpec "ImplicitParams" LangExt.ImplicitParams,
flagSpec "ImplicitPrelude" LangExt.ImplicitPrelude,
+ flagSpec "ImportQualifiedPost" LangExt.ImportQualifiedPost,
flagSpec "ImpredicativeTypes" LangExt.ImpredicativeTypes,
flagSpec' "IncoherentInstances" LangExt.IncoherentInstances
setIncoherentInsts,
diff --git a/compiler/main/HeaderInfo.hs b/compiler/main/HeaderInfo.hs
index 450ac95f96..e5e5efd753 100644
--- a/compiler/main/HeaderInfo.hs
+++ b/compiler/main/HeaderInfo.hs
@@ -131,7 +131,7 @@ mkPrelImports this_mod loc implicit_prelude import_decls
ideclPkgQual = Nothing,
ideclSource = False,
ideclSafe = False, -- Not a safe import
- ideclQualified = False,
+ ideclQualified = NotQualified,
ideclImplicit = True, -- Implicit!
ideclAs = Nothing,
ideclHiding = Nothing }
diff --git a/compiler/main/HscStats.hs b/compiler/main/HscStats.hs
index 44edb82c5e..fdd5ee78e2 100644
--- a/compiler/main/HscStats.hs
+++ b/compiler/main/HscStats.hs
@@ -126,9 +126,10 @@ ppSourceStats short (dL->L _ (HsModule _ exports imports ldecls _ _))
import_info _ = panic " import_info: Impossible Match"
-- due to #15884
- safe_info = qual_info
- qual_info False = 0
- qual_info True = 1
+ safe_info False = 0
+ safe_info True = 1
+ qual_info NotQualified = 0
+ qual_info _ = 1
as_info Nothing = 0
as_info (Just _) = 1
spec_info Nothing = (0,0,0,0,1,0,0)
diff --git a/compiler/parser/Lexer.x b/compiler/parser/Lexer.x
index 3c1ea8cc7d..edad2d90d7 100644
--- a/compiler/parser/Lexer.x
+++ b/compiler/parser/Lexer.x
@@ -2329,6 +2329,7 @@ data ExtBits
| DoAndIfThenElseBit
| MultiWayIfBit
| GadtSyntaxBit
+ | ImportQualifiedPostBit
-- Flags that are updated once parsing starts
| InRulePragBit
@@ -2415,6 +2416,7 @@ mkParserFlags' warningFlags extensionFlags thisPackage
.|. DoAndIfThenElseBit `xoptBit` LangExt.DoAndIfThenElse
.|. MultiWayIfBit `xoptBit` LangExt.MultiWayIf
.|. GadtSyntaxBit `xoptBit` LangExt.GADTSyntax
+ .|. ImportQualifiedPostBit `xoptBit` LangExt.ImportQualifiedPost
optBits =
HaddockBit `setBitIf` isHaddock
.|. RawTokenStreamBit `setBitIf` rawTokStream
diff --git a/compiler/parser/Parser.y b/compiler/parser/Parser.y
index e6f639edb3..c2dae02afc 100644
--- a/compiler/parser/Parser.y
+++ b/compiler/parser/Parser.y
@@ -39,6 +39,7 @@ module Parser (parseModule, parseSignature, parseImport, parseStatement, parseBa
import Control.Monad ( unless, liftM, when, (<=<) )
import GHC.Exts
import Data.Char
+import Data.Maybe ( maybeToList )
import Control.Monad ( mplus )
import Control.Applicative ((<$))
@@ -955,17 +956,22 @@ importdecls_semi
| {- empty -} { [] }
importdecl :: { LImportDecl GhcPs }
- : 'import' maybe_src maybe_safe optqualified maybe_pkg modid maybeas maybeimpspec
- {% ams (cL (comb4 $1 $6 (snd $7) $8) $
- ImportDecl { ideclExt = noExt
- , ideclSourceSrc = snd $ fst $2
- , ideclName = $6, ideclPkgQual = snd $5
- , ideclSource = snd $2, ideclSafe = snd $3
- , ideclQualified = snd $4, ideclImplicit = False
- , ideclAs = unLoc (snd $7)
- , ideclHiding = unLoc $8 })
- ((mj AnnImport $1 : (fst $ fst $2) ++ fst $3 ++ fst $4
- ++ fst $5 ++ fst $7)) }
+ : 'import' maybe_src maybe_safe optqualified maybe_pkg modid optqualified maybeas maybeimpspec
+ {% do {
+ ; checkImportDecl $4 $7
+ ; ams (cL (comb4 $1 $6 (snd $8) $9) $
+ ImportDecl { ideclExt = noExt
+ , ideclSourceSrc = snd $ fst $2
+ , ideclName = $6, ideclPkgQual = snd $5
+ , ideclSource = snd $2, ideclSafe = snd $3
+ , ideclQualified = importDeclQualifiedStyle $4 $7
+ , ideclImplicit = False
+ , ideclAs = unLoc (snd $8)
+ , ideclHiding = unLoc $9 })
+ ((mj AnnImport $1 : fst (fst $2) ++ fst $3 ++ fmap (mj AnnQualified) (maybeToList $4)
+ ++ fst $5 ++ fmap (mj AnnQualified) (maybeToList $7) ++ fst $8))
+ }
+ }
maybe_src :: { (([AddAnn],SourceText),IsBootInterface) }
: '{-# SOURCE' '#-}' { (([mo $1,mc $2],getSOURCE_PRAGs $1)
@@ -986,9 +992,9 @@ maybe_pkg :: { ([AddAnn],Maybe StringLiteral) }
; return ([mj AnnPackageName $1], Just (StringLiteral (getSTRINGs $1) pkgFS)) } }
| {- empty -} { ([],Nothing) }
-optqualified :: { ([AddAnn],Bool) }
- : 'qualified' { ([mj AnnQualified $1],True) }
- | {- empty -} { ([],False) }
+optqualified :: { Maybe (Located Token) }
+ : 'qualified' { Just $1 }
+ | {- empty -} { Nothing }
maybeas :: { ([AddAnn],Located (Maybe (Located ModuleName))) }
: 'as' modid { ([mj AnnAs $1]
diff --git a/compiler/parser/RdrHsSyn.hs b/compiler/parser/RdrHsSyn.hs
index 156931dc9f..490fed0384 100644
--- a/compiler/parser/RdrHsSyn.hs
+++ b/compiler/parser/RdrHsSyn.hs
@@ -49,6 +49,7 @@ module RdrHsSyn (
-- Bunch of functions in the parser monad for
-- checking and constructing values
+ checkImportDecl,
checkExpBlockArguments,
checkPrecP, -- Int -> P Int
checkContext, -- HsType -> P HsContext
@@ -81,7 +82,10 @@ module RdrHsSyn (
-- Warnings and errors
warnStarIsType,
+ warnPrepositiveQualifiedModule,
failOpFewArgs,
+ failOpNotEnabledImportQualifiedPost,
+ failOpImportQualifiedTwice,
SumOrTuple (..),
@@ -1051,6 +1055,31 @@ checkNoDocs msg ty = go ty
, text "on", msg, quotes (ppr t) ]
go _ = pure ()
+checkImportDecl :: Maybe (Located Token)
+ -> Maybe (Located Token)
+ -> P ()
+checkImportDecl mPre mPost = do
+ let whenJust mg f = maybe (pure ()) f mg
+
+ importQualifiedPostEnabled <- getBit ImportQualifiedPostBit
+
+ -- Error if 'qualified' found in postpostive position and
+ -- 'ImportQualifiedPost' is not in effect.
+ whenJust mPost $ \post ->
+ when (not importQualifiedPostEnabled) $
+ failOpNotEnabledImportQualifiedPost (getLoc post)
+
+ -- Error if 'qualified' occurs in both pre and postpositive
+ -- positions.
+ whenJust mPost $ \post ->
+ when (isJust mPre) $
+ failOpImportQualifiedTwice (getLoc post)
+
+ -- Warn if 'qualified' found in prepositive position and
+ -- 'Opt_WarnPrepositiveQualifiedModule' is enabled.
+ whenJust mPre $ \pre ->
+ warnPrepositiveQualifiedModule (getLoc pre)
+
-- -------------------------------------------------------------------------
-- Checking Patterns.
@@ -2945,6 +2974,27 @@ isImpExpQcWildcard _ = False
-----------------------------------------------------------------------------
-- Warnings and failures
+warnPrepositiveQualifiedModule :: SrcSpan -> P ()
+warnPrepositiveQualifiedModule span =
+ addWarning Opt_WarnPrepositiveQualifiedModule span msg
+ where
+ msg = text "Found" <+> quotes (text "qualified")
+ <+> text "in prepositive position"
+ $$ text "Suggested fix: place " <+> quotes (text "qualified")
+ <+> text "after the module name instead."
+
+failOpNotEnabledImportQualifiedPost :: SrcSpan -> P ()
+failOpNotEnabledImportQualifiedPost loc = addError loc msg
+ where
+ msg = text "Found" <+> quotes (text "qualified")
+ <+> text "in postpositive position. "
+ $$ text "To allow this, enable language extension 'ImportQualifiedPost'"
+
+failOpImportQualifiedTwice :: SrcSpan -> P ()
+failOpImportQualifiedTwice loc = addError loc msg
+ where
+ msg = text "Multiple occurences of 'qualified'"
+
warnStarIsType :: SrcSpan -> P ()
warnStarIsType span = addWarning Opt_WarnStarIsType span msg
where
diff --git a/compiler/rename/RnNames.hs b/compiler/rename/RnNames.hs
index 7c0c6759ea..9a69423209 100644
--- a/compiler/rename/RnNames.hs
+++ b/compiler/rename/RnNames.hs
@@ -267,7 +267,7 @@ rnImportDecl this_mod
, ideclName = loc_imp_mod_name
, ideclPkgQual = mb_pkg
, ideclSource = want_boot, ideclSafe = mod_safe
- , ideclQualified = qual_only, ideclImplicit = implicit
+ , ideclQualified = qual_style, ideclImplicit = implicit
, ideclAs = as_mod, ideclHiding = imp_details }))
= setSrcSpan loc $ do
@@ -275,6 +275,8 @@ rnImportDecl this_mod
pkg_imports <- xoptM LangExt.PackageImports
when (not pkg_imports) $ addErr packageImportErr
+ let qual_only = isImportDeclQualified qual_style
+
-- If there's an error in loadInterface, (e.g. interface
-- file not found) we get lots of spurious errors from 'filterImports'
let imp_mod_name = unLoc loc_imp_mod_name
@@ -1470,8 +1472,8 @@ warnUnusedImport flag fld_env (L loc decl, used, unused)
, text "from module" <+> quotes pp_mod <+> is_redundant]
pp_herald = text "The" <+> pp_qual <+> text "import of"
pp_qual
- | ideclQualified decl = text "qualified"
- | otherwise = Outputable.empty
+ | isImportDeclQualified (ideclQualified decl)= text "qualified"
+ | otherwise = Outputable.empty
pp_mod = ppr (unLoc (ideclName decl))
is_redundant = text "is redundant"
diff --git a/compiler/typecheck/TcRnDriver.hs b/compiler/typecheck/TcRnDriver.hs
index 00765b6a2f..e3869d2711 100644
--- a/compiler/typecheck/TcRnDriver.hs
+++ b/compiler/typecheck/TcRnDriver.hs
@@ -1567,7 +1567,7 @@ tcPreludeClashWarn warnFlag name = do
-- Unqualified import?
isUnqualified :: ImportDecl GhcRn -> Bool
- isUnqualified = not . ideclQualified
+ isUnqualified = not . isImportDeclQualified . ideclQualified
-- List of explicitly imported (or hidden) Names from a single import.
-- Nothing -> No explicit imports