Skip to content

Commit

Permalink
Add support for NumericUnderscores extensions from CLI/config
Browse files Browse the repository at this point in the history
  • Loading branch information
friedbrice authored and 9999years committed Oct 24, 2024
1 parent ad9a1f8 commit d296351
Show file tree
Hide file tree
Showing 6 changed files with 27 additions and 10 deletions.
21 changes: 15 additions & 6 deletions src/GHC/All.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,7 +6,9 @@ module GHC.All(
CppFlags(..), ParseFlags(..), defaultParseFlags,
parseFlagsAddFixities, parseFlagsSetLanguage,
ParseError(..), ModuleEx(..),
parseModuleEx, createModuleEx, createModuleExWithFixities, ghcComments, modComments, firstDeclComments,
parseModuleEx, createModuleEx, createModuleExWithFixities,
createModuleExWithFixitiesAndExtensions, ghcComments, modComments,
firstDeclComments,
parseExpGhcWithMode, parseImportDeclGhcWithMode, parseDeclGhcWithMode,
) where

Expand Down Expand Up @@ -86,8 +88,9 @@ data ParseError = ParseError
}

-- | Result of 'parseModuleEx', representing a parsed module.
newtype ModuleEx = ModuleEx {
ghcModule :: Located (HsModule GhcPs)
data ModuleEx = ModuleEx {
ghcModule :: Located (HsModule GhcPs),
configuredExtensions :: [Extension]
}

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

createModuleExWithFixities :: [(String, Fixity)] -> Located (HsModule GhcPs) -> ModuleEx
createModuleExWithFixities fixities ast =
ModuleEx (applyFixities (fixitiesFromModule ast ++ fixities) ast)
createModuleExWithFixities = createModuleExWithFixitiesAndExtensions []

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

-- | Parse a Haskell module. Applies the C pre processor, and uses
-- best-guess fixity resolution if there are ambiguities. The
Expand Down Expand Up @@ -197,7 +206,7 @@ parseModuleEx flags file str = timedIO "Parse" file $ runExceptT $ do
ExceptT $ parseFailureErr dynFlags str file str $ NE.fromList errs
else do
let fixes = fixitiesFromModule a ++ ghcFixitiesFromParseFlags flags
pure $ ModuleEx (applyFixities fixes a)
pure $ ModuleEx (applyFixities fixes a) (enabledExtensions flags)
PFailed s ->
ExceptT $ parseFailureErr dynFlags str file str $ NE.fromList . bagToList . getMessages $ GhcPsMessage <$> snd (getPsMessages s)
where
Expand Down
2 changes: 1 addition & 1 deletion src/Hint/Duplicate.hs
Original file line number Diff line number Diff line change
Expand Up @@ -58,7 +58,7 @@ duplicateHint ms =
]
where
ds = [(modName m, fromMaybe "" (declName d), unLoc d)
| ModuleEx m <- map snd ms
| ModuleEx m _ <- map snd ms
, d <- hsmodDecls (unLoc m)]

dupes :: (Outputable e, Data e) => [(String, String, [LocatedA e])] -> [Idea]
Expand Down
2 changes: 1 addition & 1 deletion src/Hint/Export.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,7 +21,7 @@ import GHC.Types.Name.Occurrence
import GHC.Types.Name.Reader

exportHint :: ModuHint
exportHint _ (ModuleEx (L s m@HsModule {hsmodName = Just name, hsmodExports = exports}) )
exportHint _ (ModuleEx (L s m@HsModule {hsmodName = Just name, hsmodExports = exports}) _)
| Nothing <- exports =
let r = o{ hsmodExports = Just (noLocA [noLocA (IEModuleContents (Nothing, noAnn) name)] )} in
[(ignore "Use module export list" (L s o) (noLoc r) []){ideaNote = [Note "an explicit list is usually better"]}]
Expand Down
8 changes: 8 additions & 0 deletions src/Hint/NumLiteral.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,13 +21,15 @@

module Hint.NumLiteral (numLiteralHint) where

import GHC.All (configuredExtensions)
import GHC.Hs
import GHC.Data.FastString
import GHC.LanguageExtensions.Type (Extension (..))
import GHC.Types.SrcLoc
import GHC.Types.SourceText
import GHC.Util.ApiAnnotation (extensions)
import Data.Char (isDigit, isOctDigit, isHexDigit)
import Data.Foldable (toList)
import Data.List (intercalate)
import Data.Set (union)
import Data.Generics.Uniplate.DataOnly (universeBi)
Expand All @@ -43,10 +45,16 @@ numLiteralHint _ modu =
-- not the module so to be safe, look also at `firstDeclComments
-- modu` (https://gitlab.haskell.org/ghc/ghc/-/merge_requests/9517).
let exts = union (extensions (modComments modu)) (extensions (firstDeclComments modu)) in
-- TODO: there's a subtle bug when the module disables `NumericUnderscores`.
-- This seems pathological, though, because who would enable it for their
-- project but disable it in specific files?
if NumericUnderscores `elem` exts then
concatMap suggestUnderscore . universeBi
else
const []
where
moduleExtensions = union (extensions (modComments modu)) (extensions (firstDeclComments modu))
activeExtensions = configuredExtensions modu <> toList moduleExtensions

suggestUnderscore :: LHsExpr GhcPs -> [Idea]
suggestUnderscore x@(L _ (HsOverLit _ ol@(OverLit _ (HsIntegral intLit@(IL (SourceText srcTxt) _ _))))) =
Expand Down
2 changes: 1 addition & 1 deletion src/Hint/Unsafe.hs
Original file line number Diff line number Diff line change
Expand Up @@ -46,7 +46,7 @@ import Language.Haskell.GhclibParserEx.GHC.Utils.Outputable
-- @
-- is. We advise that such constants should have a @NOINLINE@ pragma.
unsafeHint :: DeclHint
unsafeHint _ (ModuleEx (L _ m)) = \ld@(L loc d) ->
unsafeHint _ (ModuleEx (L _ m) _) = \ld@(L loc d) ->
[rawIdea Hint.Type.Warning "Missing NOINLINE pragma" (locA loc)
(unsafePrettyPrint d)
(Just $ trimStart (unsafePrettyPrint $ gen x) ++ "\n" ++ unsafePrettyPrint d)
Expand Down
2 changes: 1 addition & 1 deletion src/Language/Haskell/HLint.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,7 +24,7 @@ module Language.Haskell.HLint(
-- * Hints
Hint,
-- * Modules
ModuleEx, parseModuleEx, createModuleEx, createModuleExWithFixities, ParseError(..),
ModuleEx, parseModuleEx, createModuleEx, createModuleExWithFixities, createModuleExWithFixitiesAndExtensions, ParseError(..),
-- * Parse flags
defaultParseFlags,
ParseFlags(..), CppFlags(..), FixityInfo,
Expand Down

0 comments on commit d296351

Please sign in to comment.