{-| Module : Settings Description : For operations regarding file system io Copyright : Copyright (C) 2017-2019 S. Kamps License : -- This file is distributed under the terms of the Apache License 2.0. For more information, see the file "LICENSE", which is included in the distribution. Stability : experimental -} module Settings where import Data.Char import System.Console.GetOpt import System.Environment import System.Exit -- | Analyse the evolution of a Haskell repository: Information on program-level. -- Analyse the distribution on module level data AnalysisType = Evolution | Distribution deriving Show -- | LCOM measures module cohesion, CBO measures module coupling, LOC measures module size in pure lines of code data MetricType = LCOM | CBO | LOC deriving Show -- | The settings required for the Implementation Under Test. data Settings = Settings { programName :: String -- ^ The Implementation Under Test name. , version :: String -- ^ The Implementation Under Test snapshot version. , commitHash :: String -- ^ The commit hash of the snapshot, currently analysed. , analysis :: AnalysisType -- ^ The type of analysis. , metricType :: MetricType -- ^ The metric to be used in the analysis. } deriving Show defaultSettings :: String -> Settings defaultSettings name = Settings name "" "" Distribution LOC settings :: [OptDescr (Settings -> Settings)] settings = [ Option "v" ["version"] (ReqArg (\v set -> set { version = v }) "STRING") "version of snapshot" , Option "" ["hash"] (ReqArg (\h set -> set { commitHash = h }) "STRING") "commit hash of snapshot" , Option "" ["evolution"] (NoArg (\set -> set { analysis = Evolution } )) "evolution analysis type" , Option "" ["lcom"] (NoArg (\set -> set { metricType = LCOM } )) "LCOM metric (module cohesion)" , Option "" ["cbo"] (NoArg (\set -> set { metricType = CBO } )) "CBO metric (module coupling)" , Option "" ["loc"] (NoArg (\set -> set { metricType = LOC } )) "LOC metric (module lines of code)" ] getSettings :: IO Settings getSettings = do args <- getArgs case getOpt Permute settings args of -- legacy: 5 arguments ([], [name, vers, hash, ana, metric], []) -> return $ Settings { programName = name , version = vers , commitHash = hash , analysis = readAnalysisType ana , metricType = readMetricType metric } -- command-line options (fs, [name], []) -> return $ foldl (flip id) (defaultSettings name) fs -- errors/usage info (_, _, errs) -> do putStrLn $ concat errs ++ usageInfo header settings exitFailure where header = "Usage: haskellanalysis [options] file" readAnalysisType :: String -> AnalysisType readAnalysisType s = case map toLower s of "evolution" -> Evolution "distribution" -> Distribution _ -> error $ "Unknown analysis type " ++ s readMetricType :: String -> MetricType readMetricType s = case map toLower s of "lcom" -> LCOM "cbo" -> CBO "loc" -> LOC _ -> error $ "Unknown metric type " ++ s