{-| Module : $Header$ Stability : experimental Portability : non-portable Entry point for time series analysis executable. Borrowed from the 2006-zhao_xiaojian's paper, use case is to answer a question like: /Which pairs of streams were corrrelated with a value of over 0.9 for the last hour?/ Try: $ time-series -i data/correlated-walks_rho09_n100000_k5.csv -} module Main where import Control.Monad import Data.Char (toLower) import Data.Word import System.Environment (getArgs) import System.Exit import System.Console.GetOpt import System.IO import TimeSeries.Routing import TimeSeries.Scratch import TimeSeries.Utils -- | Command line arguments. data Args = InFile FilePath | OutFile FilePath | SketchSize Int | SketchGroups Word8 | CorrCutoff Double | SWSize Word64 | BWSize Word64 | RandSeed Integer | Impl Implementation | Help | Verbose | DistRatio | CorrDiff | Incr deriving (Eq, Show, Read) -- | The default. defaultConfig :: Config defaultConfig = Config { sketchSize = 64 , sketchGroups = 4 , corrCutoff = 0.95 , swSize = 256 , bwSize = 32 , randSeed = 0x12345678 , impls = Direct , verbose = False } {- XXX: Bootstrap? -} -- | Available options, config values and Help. options :: [OptDescr Args] options = [ Option ['i'] ["infile"] (ReqArg InFile "FILE") "CSV filepath for input" , Option ['o'] ["outfile"] (ReqArg OutFile "FILE") "Output file path to write results (default: stdout)" , Option ['s'] ["sketch"] (ReqArg (SketchSize . read) "INT") "Sketch size (default: 64)" , Option ['g'] ["group"] (ReqArg (SketchGroups . read) "INT") "Number of sketch groups (default: 4)" , Option ['c'] ["cutoff"] (ReqArg (CorrCutoff . read) "DOUBLE") "Correlation cutoff, between 0 to 1 (default: 0.95)" , Option ['w'] ["swsize"] (ReqArg (SWSize . read) "INT") "Sliding window size (default: 256)" , Option ['b'] ["bwsize"] (ReqArg (BWSize . read) "INT") "Basic window size (default: 32)" , Option ['r'] ["rand"] (ReqArg (RandSeed . read) "INT") "Random seed (default: 0x12345678)" , Option [] ["impl"] (ReqArg impl "direct|sketch") "Choose implementation (default: direct) " , Option ['h'] ["help"] (NoArg Help) "Show this help" , Option [] ["verbose"] (NoArg Verbose) "Show verbose output" , Option [] ["distratio"] (NoArg DistRatio) "Print direct / sketch distance ratio and exit" , Option [] ["corrdiff"] (NoArg CorrDiff) "Print \"abs (direct - sketch)\" correlation and exit" , Option [] ["incr"] (NoArg Incr) "Print sample comparison of incremental sketches and exit" ] impl :: String -> Args impl str = case map toLower str of "direct" -> Impl Direct "sketch" -> Impl Sketch _ -> error msg where msg = unlines [ "Unknown implementation: " ++ str , "Available impl: direct, sketch" ] -- | Handle options and update config and input filepath. handleArgs :: (Config, FilePath, FilePath) -> [Args] -> (Config, FilePath, FilePath) handleArgs confs = foldr f confs where f arg (c,ipath,opath) = case arg of InFile ipath' -> (c, ipath',opath) OutFile opath' -> (c, ipath, opath') SketchSize n -> (c {sketchSize=n}, ipath, opath) SketchGroups n -> (c {sketchGroups=n}, ipath, opath) CorrCutoff d -> (c {corrCutoff=d}, ipath, opath) SWSize n -> (c {swSize=n}, ipath, opath) BWSize n -> (c {bwSize=n}, ipath, opath) RandSeed n -> (c {randSeed=n}, ipath, opath) Impl i -> (c {impls=i}, ipath, opath) Verbose -> (c {verbose=True}, ipath, opath) _ -> (c, ipath, opath) -- | Show brief usage. printUsage :: IO () printUsage = putStrLn $ usageInfo header options where header = unlines ["time-series: time series analysis" , "" , "OPTIONS:" ] main :: IO () main = do let defaultArgs = (defaultConfig, "", "-") args <- getArgs (conf,ipath,opath) <- case getOpt Permute options args of (os,_,es) | not (null es) -> mapM_ putStrLn es >> exitFailure | Help `elem` os -> printUsage >> exitSuccess | DistRatio `elem` os -> print_dist_ratios >> exitSuccess | CorrDiff `elem` os -> print_corr_diffs >> exitSuccess | Incr `elem` os -> print_comparisons_incr >> exitSuccess | otherwise -> return $ handleArgs defaultArgs os when (null ipath) $ putStrLn "No input file given, exiting" >> printUsage >> exitFailure csvData <- readFile ipath let work hdl = loop hdl conf (formatCSV csvData) case opath of "-" -> work stdout _ -> withFile opath WriteMode work