Copyright | (c) 2015 Michele Lacchia |
---|---|
License | ISC |
Maintainer | Michele Lacchia <michelelacchia@gmail.com> |
Stability | alpha |
Portability | portable |
Safe Haskell | None |
Language | Haskell2010 |
Programmatic interface to Argon.
- type AnalysisResult = Either String [ComplexityBlock]
- newtype ComplexityBlock = CC (Loc, String, Int)
- data OutputMode
- data Config = Config {
- minCC :: Int
- exts :: [ExtensionFlag]
- headers :: [FilePath]
- includeDirs :: [FilePath]
- outputMode :: OutputMode
- defaultConfig :: Config
- type Loc = (Int, Int)
- type LModule = Located (HsModule RdrName)
- allFiles :: (MonadIO m, MonadSafe m) => FilePath -> Producer FilePath m ()
- analyze :: Config -> FilePath -> IO (FilePath, AnalysisResult)
- parseModule :: Config -> FilePath -> IO (Either String LModule)
- parseExts :: FilePath -> IO [ExtensionFlag]
- flagsMap :: Map String ExtensionFlag
- order :: [ComplexityBlock] -> [ComplexityBlock]
- filterResults :: Config -> (FilePath, AnalysisResult) -> (FilePath, AnalysisResult)
- filterNulls :: (FilePath, AnalysisResult) -> Bool
- exportStream :: MonadIO m => Config -> Producer (FilePath, AnalysisResult) m () -> Effect m ()
- bareTextFormatter :: MonadIO m => Pipe (FilePath, AnalysisResult) String m ()
- coloredTextFormatter :: MonadIO m => Pipe (FilePath, AnalysisResult) String m ()
- srcSpanToLoc :: SrcSpan -> Loc
- locToString :: Loc -> String
- tagMsg :: Loc -> String -> String
Types
type AnalysisResult = Either String [ComplexityBlock] Source
Represent the result of the analysis of one file.
It can either be an error message or a list of
ComplexityBlock
s.
newtype ComplexityBlock Source
Hold the data associated to a function binding:
(location, function name, complexity)
.
data OutputMode Source
Type describing how the results should be exported.
Type holding all the options passed from the command line.
Config | |
|
defaultConfig :: Config Source
Default configuration options.
Warning: These are not Argon's default options.
Type synonym representing a location in the source code. The tuple
represents the following: (start line, start col)
.
type LModule = Located (HsModule RdrName) Source
Type synonym for a syntax node representing a module tagged with a
SrcSpan
Gathering source files
allFiles :: (MonadIO m, MonadSafe m) => FilePath -> Producer FilePath m () Source
Starting from a path, generate a sequence of paths corresponding to Haskell files. The filesystem is traversed depth-first.
Parsing
:: Config | Configuration options |
-> FilePath | The filename corresponding to the source code |
-> IO (FilePath, AnalysisResult) |
Parse the code in the given filename and compute cyclomatic complexity for every function binding.
parseModule :: Config -> FilePath -> IO (Either String LModule) Source
Parse a module with the default instructions for the C pre-processor Only the includes directory is taken from the config
parseExts :: FilePath -> IO [ExtensionFlag] Source
Parse the given Cabal file generate a list of GHC extension flags. The extension names are read from the default-extensions field in the library section.
Manipulating results
order :: [ComplexityBlock] -> [ComplexityBlock] Source
Order a list of blocks. Ordering is done with respect to:
- complexity (descending)
- line number (ascending)
- function name (alphabetically)
filterResults :: Config -> (FilePath, AnalysisResult) -> (FilePath, AnalysisResult) Source
Filter the results of the analysis, with respect to the given
Config
.
filterNulls :: (FilePath, AnalysisResult) -> Bool Source
A result is discarded if it correspond to a successful analysis and there are no blocks to show
exportStream :: MonadIO m => Config -> Producer (FilePath, AnalysisResult) m () -> Effect m () Source
Export analysis' results. How to export the data is defined by the
Config
parameter.
Formatting results
bareTextFormatter :: MonadIO m => Pipe (FilePath, AnalysisResult) String m () Source
coloredTextFormatter :: MonadIO m => Pipe (FilePath, AnalysisResult) String m () Source
Utilities
srcSpanToLoc :: SrcSpan -> Loc Source
Convert a GHC's SrcSpan
to a (line, column)
pair. In case of a GHC's
"bad span" the resulting pair is (0, 0)
.
locToString :: Loc -> String Source
Convert a location to a string of the form "line:col"