argon-0.4.1.0: Measure your code's complexity

Copyright(c) 2015 Michele Lacchia
LicenseISC
MaintainerMichele Lacchia <michelelacchia@gmail.com>
Stabilityalpha
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

Argon

Contents

Description

Programmatic interface to Argon.

Synopsis

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 ComplexityBlocks.

newtype ComplexityBlock Source

Hold the data associated to a function binding: (location, function name, complexity).

Constructors

CC (Loc, String, Int) 

data OutputMode Source

Type describing how the results should be exported.

Constructors

BareText

Text-only output, no colors.

Colored

Text-only output, with colors.

JSON

Data is serialized to JSON.

data Config Source

Type holding all the options passed from the command line.

Constructors

Config 

Fields

minCC :: Int

Minimum complexity a block has to have to be shown in results.

exts :: [ExtensionFlag]

Path to the main Cabal file

headers :: [FilePath]

Header files to be automatically included before preprocessing

includeDirs :: [FilePath]

Additional include directories for the C preprocessor

outputMode :: OutputMode

Describe how the results should be exported.

defaultConfig :: Config Source

Default configuration options.

Warning: These are not Argon's default options.

type Loc = (Int, Int) Source

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

analyze Source

Arguments

:: 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.

flagsMap :: Map String ExtensionFlag Source

A Map from extensions names to extensions flags

Manipulating results

order :: [ComplexityBlock] -> [ComplexityBlock] Source

Order a list of blocks. Ordering is done with respect to:

  1. complexity (descending)
  2. line number (ascending)
  3. 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

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"

tagMsg :: Loc -> String -> String Source

Add the location to a string message