hlint-2.1.25: Source code suggestions

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.HLint3

Contents

Description

WARNING: This module represents a previous version of the HLint API. Please use Language.Haskell.HLint4 instead.

Synopsis

Documentation

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 -> [(Module SrcSpanInfo, [Comment])] -> [Idea] Source #

Given a way of classifying results, and a Hint, apply to a set of modules generating a list of Ideas. 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

data Idea Source #

An idea suggest by a Hint.

Constructors

Idea 

Fields

Instances
Eq Idea Source # 
Instance details

Defined in Idea

Methods

(==) :: Idea -> Idea -> Bool #

(/=) :: Idea -> Idea -> Bool #

Ord Idea Source # 
Instance details

Defined in Idea

Methods

compare :: Idea -> Idea -> Ordering #

(<) :: Idea -> Idea -> Bool #

(<=) :: Idea -> Idea -> Bool #

(>) :: Idea -> Idea -> Bool #

(>=) :: Idea -> Idea -> Bool #

max :: Idea -> Idea -> Idea #

min :: Idea -> Idea -> Idea #

Show Idea Source # 
Instance details

Defined in Idea

Methods

showsPrec :: Int -> Idea -> ShowS #

show :: Idea -> String #

showList :: [Idea] -> ShowS #

data Severity Source #

How severe an issue is.

Constructors

Ignore

The issue has been explicitly ignored and will usually be hidden (pass --show on the command line to see ignored ideas).

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.

data Note Source #

A note describing the impact of the replacement.

Constructors

IncreasesLaziness

The replacement is increases laziness, for example replacing reverse (reverse x) with x makes the code lazier.

DecreasesLaziness

The replacement is decreases laziness, for example replacing (fst x, snd x) with x makes the code stricter.

RemovesError String

The replacement removes errors, for example replacing foldr1 (+) with sum removes an error on [], and might contain the text "on []".

ValidInstance String String

The replacement assumes standard type class lemmas, a hint with the note ValidInstance "Eq" "x" might only be valid if the x variable has a reflexive Eq instance.

RequiresExtension String

The replacement requires this extension to be available.

Note String

An arbitrary note.

Instances
Eq Note Source # 
Instance details

Defined in Config.Type

Methods

(==) :: Note -> Note -> Bool #

(/=) :: Note -> Note -> Bool #

Ord Note Source # 
Instance details

Defined in Config.Type

Methods

compare :: Note -> Note -> Ordering #

(<) :: Note -> Note -> Bool #

(<=) :: Note -> Note -> Bool #

(>) :: Note -> Note -> Bool #

(>=) :: Note -> Note -> Bool #

max :: Note -> Note -> Note #

min :: Note -> Note -> Note #

Show Note Source # 
Instance details

Defined in Config.Type

Methods

showsPrec :: Int -> Note -> ShowS #

show :: Note -> String #

showList :: [Note] -> ShowS #

Settings

data Classify Source #

How to classify an Idea. If any matching field is "" then it matches everything.

Constructors

Classify 

Fields

Instances
Show Classify Source # 
Instance details

Defined in Config.Type

getHLintDataDir :: IO FilePath Source #

Get the Cabal configured data directory of HLint.

autoSettings :: IO (ParseFlags, [Classify], Hint) Source #

The function produces a tuple containg ParseFlags (for parseModuleEx), and Classify and Hint for applyHints. It approximates the normal HLint configuration steps, roughly:

  1. Use findSettings with readSettingsFile to find and load the HLint settings files.
  2. Use parseFlagsAddFixities and resolveHints to transform the outputs of findSettings.

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 ([Fixity], [Classify], [Either HintBuiltin HintRule]) 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

data HintBuiltin Source #

A list of the builtin hints wired into HLint. This list is likely to grow over time.

data HintRule Source #

A LHS ==> RHS style hint rule.

Constructors

HintRule 

Fields

Instances
Show HintRule Source # 
Instance details

Defined in Config.Type

data Hint Source #

Functions to generate hints, combined using the Monoid instance.

Constructors

Hint 

Fields

Instances
Semigroup Hint Source # 
Instance details

Defined in Hint.Type

Methods

(<>) :: Hint -> Hint -> Hint #

sconcat :: NonEmpty Hint -> Hint #

stimes :: Integral b => b -> Hint -> Hint #

Monoid Hint Source # 
Instance details

Defined in Hint.Type

Methods

mempty :: Hint #

mappend :: Hint -> Hint -> Hint #

mconcat :: [Hint] -> Hint #

Scopes

data Scope Source #

Data type representing the modules in scope within a module. Created with scopeCreate and queried with scopeMatch and scopeMove. Note that the mempty Scope is not equivalent to scopeCreate on an empty module, due to the implicit import of Prelude.

Instances
Show Scope Source # 
Instance details

Defined in HSE.Scope

Methods

showsPrec :: Int -> Scope -> ShowS #

show :: Scope -> String #

showList :: [Scope] -> ShowS #

Semigroup Scope Source # 
Instance details

Defined in HSE.Scope

Methods

(<>) :: Scope -> Scope -> Scope #

sconcat :: NonEmpty Scope -> Scope #

stimes :: Integral b => b -> Scope -> Scope #

Monoid Scope Source # 
Instance details

Defined in HSE.Scope

Methods

mempty :: Scope #

mappend :: Scope -> Scope -> Scope #

mconcat :: [Scope] -> Scope #

scopeCreate :: Module SrcSpanInfo -> Scope Source #

Create a Scope value from a module, based on the modules imports.

scopeMatch :: (Scope, QName S) -> (Scope, QName S) -> Bool Source #

Given a two names in scopes, could they possibly refer to the same thing. This property is reflexive.

scopeMove :: (Scope, QName S) -> Scope -> QName S Source #

Given a name in a scope, and a new scope, create a name for the new scope that will refer to the same thing. If the resulting name is ambiguous, it picks a plausible candidate.

Haskell-src-exts

parseModuleEx :: ParseFlags -> FilePath -> Maybe String -> IO (Either ParseError (Module SrcSpanInfo, [Comment])) 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. This version uses both hs-src-exts AND ghc-lib.

parseFlagsAddFixities :: [Fixity] -> ParseFlags -> ParseFlags Source #

Given some fixities, add them to the existing fixities in ParseFlags.

data ParseError Source #

A parse error.

Constructors

ParseError 

Fields

data ParseFlags Source #

Created with defaultParseFlags, used by parseModuleEx.

Constructors

ParseFlags 

Fields

  • cppFlags :: CppFlags

    How the file is preprocessed (defaults to NoCpp).

  • hseFlags :: ParseMode

    How the file is parsed (defaults to all fixities in the base package and most non-conflicting extensions).

data CppFlags Source #

What C pre processor should be used.

Constructors

NoCpp

No pre processing is done.

CppSimple

Lines prefixed with # are stripped.

Cpphs CpphsOptions

The cpphs library is used.