Skip to content

Commit b15d5df

Browse files
friedbrice9999years
authored andcommitted
Add support for NumericUnderscores extensions from CLI/config
Closes ndmitchell#1434
1 parent 4620d86 commit b15d5df

File tree

6 files changed

+32
-16
lines changed

6 files changed

+32
-16
lines changed

src/GHC/All.hs

+15-6
Original file line numberDiff line numberDiff line change
@@ -6,7 +6,9 @@ module GHC.All(
66
CppFlags(..), ParseFlags(..), defaultParseFlags,
77
parseFlagsAddFixities, parseFlagsSetLanguage,
88
ParseError(..), ModuleEx(..),
9-
parseModuleEx, createModuleEx, createModuleExWithFixities, ghcComments, modComments, firstDeclComments,
9+
parseModuleEx, createModuleEx, createModuleExWithFixities,
10+
createModuleExWithFixitiesAndExtensions, ghcComments, modComments,
11+
firstDeclComments,
1012
parseExpGhcWithMode, parseImportDeclGhcWithMode, parseDeclGhcWithMode,
1113
) where
1214

@@ -89,8 +91,9 @@ data ParseError = ParseError
8991
}
9092

9193
-- | Result of 'parseModuleEx', representing a parsed module.
92-
newtype ModuleEx = ModuleEx {
93-
ghcModule :: Located (HsModule GhcPs)
94+
data ModuleEx = ModuleEx {
95+
ghcModule :: Located (HsModule GhcPs),
96+
configuredExtensions :: [Extension]
9497
}
9598

9699
-- | Extract a complete list of all the comments in a module.
@@ -163,8 +166,14 @@ createModuleEx :: Located (HsModule GhcPs) -> ModuleEx
163166
createModuleEx = createModuleExWithFixities (map toFixity defaultFixities)
164167

165168
createModuleExWithFixities :: [(String, Fixity)] -> Located (HsModule GhcPs) -> ModuleEx
166-
createModuleExWithFixities fixities ast =
167-
ModuleEx (applyFixities (fixitiesFromModule ast ++ fixities) ast)
169+
createModuleExWithFixities = createModuleExWithFixitiesAndExtensions []
170+
171+
-- | Create a 'ModuleEx' from a GHC module. Provide a list of custom operator
172+
-- fixities and a list of GHC extensions that should be used when parsing the module
173+
-- (if there are any extensions required other than those explicitly enabled in the module).
174+
createModuleExWithFixitiesAndExtensions :: [Extension] -> [(String, Fixity)] -> Located (HsModule GhcPs) -> ModuleEx
175+
createModuleExWithFixitiesAndExtensions extensions fixities ast =
176+
ModuleEx (applyFixities (fixitiesFromModule ast ++ fixities) ast) extensions
168177

169178
impliedEnables :: Extension -> [Extension]
170179
impliedEnables ext = case Data.List.lookup ext extensionImplications of
@@ -214,7 +223,7 @@ parseModuleEx flags file str = timedIO "Parse" file $ runExceptT $ do
214223
ExceptT $ parseFailureErr dynFlags str file str $ NE.fromList errs
215224
else do
216225
let fixes = fixitiesFromModule a ++ ghcFixitiesFromParseFlags flags
217-
pure $ ModuleEx (applyFixities fixes a)
226+
pure $ ModuleEx (applyFixities fixes a) (enabledExtensions flags)
218227
PFailed s ->
219228
ExceptT $ parseFailureErr dynFlags str file str $ NE.fromList . bagToList . getMessages $ GhcPsMessage <$> snd (getPsMessages s)
220229
where

src/Hint/Duplicate.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -57,7 +57,7 @@ duplicateHint ms =
5757
]
5858
where
5959
ds = [(modName m, fromMaybe "" (declName d), unLoc d)
60-
| ModuleEx m <- map snd ms
60+
| ModuleEx m _ <- map snd ms
6161
, d <- hsmodDecls (unLoc m)]
6262

6363
dupes :: (Outputable e, Data e) => [(String, String, [LocatedA e])] -> [Idea]

src/Hint/Export.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -21,7 +21,7 @@ import GHC.Types.Name.Occurrence
2121
import GHC.Types.Name.Reader
2222

2323
exportHint :: ModuHint
24-
exportHint _ (ModuleEx (L s m@HsModule {hsmodName = Just name, hsmodExports = exports}) )
24+
exportHint _ (ModuleEx (L s m@HsModule {hsmodName = Just name, hsmodExports = exports}) _)
2525
| Nothing <- exports =
2626
let r = o{ hsmodExports = Just (noLocA [noLocA (IEModuleContents (Nothing, noAnn) name)] )} in
2727
[(ignore "Use module export list" (L s o) (noLoc r) []){ideaNote = [Note "an explicit list is usually better"]}]

src/Hint/NumLiteral.hs

+13-6
Original file line numberDiff line numberDiff line change
@@ -21,13 +21,15 @@
2121

2222
module Hint.NumLiteral (numLiteralHint) where
2323

24+
import GHC.All (configuredExtensions)
2425
import GHC.Hs
2526
import GHC.Data.FastString
2627
import GHC.LanguageExtensions.Type (Extension (..))
2728
import GHC.Types.SrcLoc
2829
import GHC.Types.SourceText
2930
import GHC.Util.ApiAnnotation (extensions)
3031
import Data.Char (isDigit, isOctDigit, isHexDigit)
32+
import Data.Foldable (toList)
3133
import Data.List (intercalate)
3234
import Data.Set (union)
3335
import Data.Generics.Uniplate.DataOnly (universeBi)
@@ -38,15 +40,20 @@ import Idea (Idea, suggest)
3840

3941
numLiteralHint :: DeclHint
4042
numLiteralHint _ modu =
41-
-- Comments appearing without an empty line before the first
42-
-- declaration in a module are now associated with the declaration
43-
-- not the module so to be safe, look also at `firstDeclComments
44-
-- modu` (https://gitlab.haskell.org/ghc/ghc/-/merge_requests/9517).
45-
let exts = union (extensions (modComments modu)) (extensions (firstDeclComments modu)) in
46-
if NumericUnderscores `elem` exts then
43+
-- TODO: there's a subtle bug when the module disables `NumericUnderscores`.
44+
-- This seems pathological, though, because who would enable it for their
45+
-- project but disable it in specific files?
46+
if NumericUnderscores `elem` activeExtensions then
4747
concatMap suggestUnderscore . universeBi
4848
else
4949
const []
50+
where
51+
-- Comments appearing without an empty line before the first
52+
-- declaration in a module are now associated with the declaration
53+
-- not the module so to be safe, look also at `firstDeclComments
54+
-- modu` (https://gitlab.haskell.org/ghc/ghc/-/merge_requests/9517).
55+
moduleExtensions = extensions (modComments modu) `union` extensions (firstDeclComments modu)
56+
activeExtensions = configuredExtensions modu <> toList moduleExtensions
5057

5158
suggestUnderscore :: LHsExpr GhcPs -> [Idea]
5259
suggestUnderscore x@(L _ (HsOverLit _ ol@(OverLit _ (HsIntegral intLit@(IL (SourceText srcTxt) _ _))))) =

src/Hint/Unsafe.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -46,7 +46,7 @@ import Language.Haskell.GhclibParserEx.GHC.Utils.Outputable
4646
-- @
4747
-- is. We advise that such constants should have a @NOINLINE@ pragma.
4848
unsafeHint :: DeclHint
49-
unsafeHint _ (ModuleEx (L _ m)) = \ld@(L loc d) ->
49+
unsafeHint _ (ModuleEx (L _ m) _) = \ld@(L loc d) ->
5050
[rawIdea Hint.Type.Warning "Missing NOINLINE pragma" (locA loc)
5151
(unsafePrettyPrint d)
5252
(Just $ trimStart (unsafePrettyPrint $ gen x) ++ "\n" ++ unsafePrettyPrint d)

src/Language/Haskell/HLint.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -24,7 +24,7 @@ module Language.Haskell.HLint(
2424
-- * Hints
2525
Hint,
2626
-- * Modules
27-
ModuleEx, parseModuleEx, createModuleEx, createModuleExWithFixities, ParseError(..),
27+
ModuleEx, parseModuleEx, createModuleEx, createModuleExWithFixities, createModuleExWithFixitiesAndExtensions, ParseError(..),
2828
-- * Parse flags
2929
defaultParseFlags,
3030
ParseFlags(..), CppFlags(..), FixityInfo,

0 commit comments

Comments
 (0)