{-# LANGUAGE OverloadedStrings #-} module Main (main) where import Control.Exception (catch, displayException) import Control.Concurrent.Async (mapConcurrently) import System.Exit (exitFailure) import System.IO (hPutStrLn, stderr) import ReduxWise.Analysis.Types (reportTotalFunctions, reportIOBoundFunctions, reportCPUBoundFunctions) import ReduxWise.CLI.Parser (Options(..), parseOptions) import ReduxWise.Project.Discovery (discoverRustFiles, DiscoveryError) import ReduxWise.Rust.Parser (parseRustFile) import ReduxWise.Report.Generator (generateReport, writeReport) main :: IO () main = do opts <- parseOptions when (optVerbose opts) $ do putStrLn "====================================================" putStrLn "======= ReduxWise - Rust Complexity Analyzer =======" putStrLn "====================================================" putStrLn $ "Project: " ++ optProjectPath opts putStrLn $ "Output: " ++ optOutputFile opts unless (null $ optExcludeDirs opts) $ putStrLn $ "Excluding: " ++ show (optExcludeDirs opts) -- Discover Rust files result <- catch (Right <$> discoverRustFiles (optProjectPath opts) (optExcludeDirs opts) (optVerbose opts)) (\e -> return $ Left (e :: DiscoveryError)) case result of Left err -> do hPutStrLn stderr $ "Error: " ++ displayException err exitFailure Right files -> do when (optVerbose opts) $ do putStrLn "\nAnalyzing files..." -- Parse and analyze each file (in parallel, but show progress) analyses <- if optVerbose opts then do -- Verbose: show each file as it's processed mapConcurrently (\file -> do putStrLn $ " Parsing: " ++ file parseRustFile file) files else -- Non-verbose: just process in parallel mapConcurrently parseRustFile files -- Filter successful analyses let successfulAnalyses = [a | Right a <- analyses] failedCount = length analyses - length successfulAnalyses when (failedCount > 0) $ putStrLn $ "Warning: Failed to parse " ++ show failedCount ++ " file(s)" -- Generate report let report = generateReport (optProjectPath opts) successfulAnalyses -- Write JSON output writeReport (optOutputFile opts) report -- Print summary when (optVerbose opts) $ do putStrLn "\n=== Analysis Summary ===" putStrLn $ "Total files analyzed: " ++ show (length successfulAnalyses) putStrLn $ "Total functions: " ++ show (reportTotalFunctions report) putStrLn $ "IO-bound functions: " ++ show (reportIOBoundFunctions report) putStrLn $ "CPU-bound functions: " ++ show (reportCPUBoundFunctions report) putStrLn $ "\nAnalysis complete! Results written to: " ++ optOutputFile opts -- Helper functions when :: Bool -> IO () -> IO () when True action = action when False _ = return () unless :: Bool -> IO () -> IO () unless b = when (not b)