Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module provides a way to apply HLint hints. If you want to just run hlint
in-process
and collect the results see hlint
.
If you want to approximate the hlint
experience with
a more structured API try:
(flags, classify, hint) <-autoSettings
Right m <-parseModuleEx
flags "MyFile.hs" Nothing print $applyHints
classify hint [m]
Synopsis
- hlint :: [String] -> IO [Idea]
- applyHints :: [Classify] -> Hint -> [ModuleEx] -> [Idea]
- data Idea = Idea {
- ideaModule :: [String]
- ideaDecl :: [String]
- ideaSeverity :: Severity
- ideaHint :: String
- ideaSpan :: SrcSpan
- ideaFrom :: String
- ideaTo :: Maybe String
- ideaNote :: [Note]
- ideaRefactoring :: [Refactoring SrcSpan]
- data Severity
- = Ignore
- | Suggestion
- | Warning
- | Error
- data Note
- unpackSrcSpan :: SrcSpan -> Maybe (FilePath, (Int, Int), (Int, Int))
- showIdeaANSI :: Idea -> String
- data Classify = Classify {}
- getHLintDataDir :: IO FilePath
- autoSettings :: IO (ParseFlags, [Classify], Hint)
- argsSettings :: [String] -> IO (ParseFlags, [Classify], Hint)
- findSettings :: (String -> IO (FilePath, Maybe String)) -> Maybe String -> IO ([FixityInfo], [Classify], Hint)
- readSettingsFile :: Maybe FilePath -> String -> IO (FilePath, Maybe String)
- data Hint
- data ModuleEx
- parseModuleEx :: ParseFlags -> FilePath -> Maybe String -> IO (Either ParseError ModuleEx)
- createModuleEx :: Located (HsModule GhcPs) -> ModuleEx
- createModuleExWithFixities :: [(String, Fixity)] -> Located (HsModule GhcPs) -> ModuleEx
- data ParseError = ParseError {}
- defaultParseFlags :: ParseFlags
- data ParseFlags = ParseFlags {}
- data CppFlags
- type FixityInfo = (String, Associativity, Int)
- parseFlagsAddFixities :: [FixityInfo] -> ParseFlags -> ParseFlags
Generate hints
hlint :: [String] -> IO [Idea] Source #
This function takes a list of command line arguments, and returns the given hints.
To see a list of arguments type hlint --help
at the console.
This function writes to the stdout/stderr streams, unless --quiet
is specified.
As an example:
do hints <- hlint ["src", "--ignore=Use map","--quiet"] when (length hints > 3) $ error "Too many hints!"
Warning: The flags provided by HLint are relatively stable, but do not have the same API stability guarantees as the rest of the strongly-typed API. Do not run this function on your server with untrusted input.
applyHints :: [Classify] -> Hint -> [ModuleEx] -> [Idea] Source #
Given a way of classifying results, and a Hint
, apply to a set of modules generating a list of Idea
s.
The Idea
values will be ordered within a file.
Given a set of modules, it may be faster to pass each to applyHints
in a singleton list.
When given multiple modules at once this function attempts to find hints between modules,
which is slower and often pointless (by default HLint passes modules singularly, using
--cross
to pass all modules together).
Idea data type
An idea suggest by a Hint
.
Idea | |
|
How severe an issue is.
Ignore | The issue has been explicitly ignored and will usually be hidden (pass |
Suggestion | Suggestions are things that some people may consider improvements, but some may not. |
Warning | Warnings are suggestions that are nearly always a good idea to apply. |
Error | Available as a setting for the user. Only parse errors have this setting by default. |
Instances
ToJSON Severity Source # | |
Data Severity Source # | |
Defined in Config.Type gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Severity -> c Severity # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Severity # toConstr :: Severity -> Constr # dataTypeOf :: Severity -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Severity) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Severity) # gmapT :: (forall b. Data b => b -> b) -> Severity -> Severity # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Severity -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Severity -> r # gmapQ :: (forall d. Data d => d -> u) -> Severity -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Severity -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Severity -> m Severity # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Severity -> m Severity # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Severity -> m Severity # | |
Bounded Severity Source # | |
Enum Severity Source # | |
Generic Severity Source # | |
Read Severity Source # | |
Show Severity Source # | |
Eq Severity Source # | |
Ord Severity Source # | |
Defined in Config.Type | |
type Rep Severity Source # | |
Defined in Config.Type type Rep Severity = D1 ('MetaData "Severity" "Config.Type" "hlint-3.8-3om2fwq1HzU5EOBAoGKHAk" 'False) ((C1 ('MetaCons "Ignore" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Suggestion" 'PrefixI 'False) (U1 :: Type -> Type)) :+: (C1 ('MetaCons "Warning" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "Error" 'PrefixI 'False) (U1 :: Type -> Type))) |
A note describing the impact of the replacement.
IncreasesLaziness | The replacement is increases laziness, for example replacing |
DecreasesLaziness | The replacement is decreases laziness, for example replacing |
RemovesError String | The replacement removes errors, for example replacing |
ValidInstance String String | The replacement assumes standard type class lemmas, a hint with the note |
RequiresExtension String | The replacement requires this extension to be available. |
Note String | An arbitrary note. |
unpackSrcSpan :: SrcSpan -> Maybe (FilePath, (Int, Int), (Int, Int)) Source #
Unpack a SrcSpan
value. Useful to allow using the Idea
information without
adding a dependency on ghc
or ghc-lib-parser
. Unpacking gives:
(filename, (startLine, startCol), (endLine, endCol))
Following the GHC API, end column is the column after the end of the error.
Lines and columns are 1-based. Returns Nothing
if there is no helpful location information.
showIdeaANSI :: Idea -> String Source #
Show an Idea
with ANSI color codes to give syntax coloring to the Haskell code.
Settings
How to classify an Idea
. If any matching field is ""
then it matches everything.
Classify | |
|
getHLintDataDir :: IO FilePath Source #
Get the Cabal configured data directory of HLint.
autoSettings :: IO (ParseFlags, [Classify], Hint) Source #
The function produces a tuple containing ParseFlags
(for parseModuleEx
),
and Classify
and Hint
for applyHints
.
It approximates the normal HLint configuration steps, roughly:
- Use
findSettings
withreadSettingsFile
to find and load the HLint settings files. - Use
parseFlagsAddFixities
andresolveHints
to transform the outputs offindSettings
.
If you want to do anything custom (e.g. using a different data directory, storing intermediate outputs, loading hints from a database) you are expected to copy and paste this function, then change it to your needs.
argsSettings :: [String] -> IO (ParseFlags, [Classify], Hint) Source #
A version of autoSettings
which respects some of the arguments supported by HLint.
If arguments unrecognised by HLint are used it will result in an error.
Arguments which have no representation in the return type are silently ignored.
findSettings :: (String -> IO (FilePath, Maybe String)) -> Maybe String -> IO ([FixityInfo], [Classify], Hint) Source #
Given a function to load a module (typically readSettingsFile
), and a module to start from
(defaults to hlint.yaml
) find the information from all settings files.
readSettingsFile :: Maybe FilePath -> String -> IO (FilePath, Maybe String) Source #
Given a directory (or Nothing
to imply getHLintDataDir
), and a module name
(e.g. HLint.Default
), find the settings file associated with it, returning the
name of the file, and (optionally) the contents.
This function looks for all settings files starting with HLint.
in the directory
argument, and all other files relative to the current directory.
Hints
Functions to generate hints, combined using the Monoid
instance.
Modules
Result of parseModuleEx
, representing a parsed module.
parseModuleEx :: ParseFlags -> FilePath -> Maybe String -> IO (Either ParseError ModuleEx) Source #
Parse a Haskell module. Applies the C pre processor, and uses
best-guess fixity resolution if there are ambiguities. The
filename -
is treated as stdin
. Requires some flags (often
defaultParseFlags
), the filename, and optionally the contents of
that file.
Note that certain programs, e.g. main = do
successfully parse
with GHC, but then fail with an error in the renamer. These
programs will return a successful parse.
createModuleEx :: Located (HsModule GhcPs) -> ModuleEx Source #
Create a ModuleEx
from a GHC module. It is assumed the incoming
parsed module has not been adjusted to account for operator
fixities (it uses the HLint default fixities).
data ParseError Source #
A parse error.
ParseError | |
|
Parse flags
defaultParseFlags :: ParseFlags Source #
Default value for ParseFlags
.
data ParseFlags Source #
Created with defaultParseFlags
, used by parseModuleEx
.
ParseFlags | |
|
What C pre processor should be used.
CppSimple | Lines prefixed with |
Cpphs CpphsOptions | The |
type FixityInfo = (String, Associativity, Int) Source #
A Fixity definition, comprising the name the fixity applies to, the direction and the precedence. As an example, a source file containing:
infixr 3 `foo`
would create ("foo", RightAssociative, 3)
.
parseFlagsAddFixities :: [FixityInfo] -> ParseFlags -> ParseFlags Source #
Given some fixities, add them to the existing fixities in ParseFlags
.