#if __GLASGOW_HASKELL__ < 710
#endif
module Argon.Types (ComplexityBlock(CC), AnalysisResult, Config(..)
, OutputMode(..), GhcParseError(..), defaultConfig)
where
import Data.List (intercalate)
import Data.Aeson
import Data.Typeable
import Control.Exception (Exception)
import qualified DynFlags as GHC
import Argon.Loc
data GhcParseError = GhcParseError {
loc :: Loc
, msg :: String
} deriving (Typeable)
newtype ComplexityBlock = CC (Loc, String, Int)
deriving (Show, Eq, Ord)
type AnalysisResult = Either String [ComplexityBlock]
data Config = Config {
minCC :: Int
, exts :: [GHC.ExtensionFlag]
, headers :: [FilePath]
, includeDirs :: [FilePath]
, outputMode :: OutputMode
}
data OutputMode = BareText
| Colored
| JSON
deriving (Show, Eq)
defaultConfig :: Config
defaultConfig = Config { minCC = 1
, exts = []
, headers = []
, includeDirs = []
, outputMode = JSON
}
instance Exception GhcParseError
instance Show GhcParseError where
show e = tagMsg (loc e) $ fixNewlines (msg e)
where fixNewlines = intercalate "\n\t\t" . lines
instance ToJSON ComplexityBlock where
toJSON (CC ((s, c), func, cc)) =
object [ "lineno" .= s
, "col" .= c
, "name" .= func
, "complexity" .= cc
]
instance ToJSON (FilePath, AnalysisResult) where
toJSON (p, Left err) = object [ "path" .= p
, "type" .= ("error" :: String)
, "message" .= err
]
toJSON (p, Right rs) = object [ "path" .= p
, "type" .= ("result" :: String)
, "blocks" .= rs
]