|
3 | 3 | module Lichen.Count.Main where
|
4 | 4 |
|
5 | 5 | import System.Directory
|
| 6 | +import System.FilePath |
6 | 7 |
|
7 |
| -import Data.Hashable |
| 8 | +import Data.Aeson |
8 | 9 | import Data.Semigroup ((<>))
|
9 | 10 | import qualified Data.Text as T
|
10 |
| -import qualified Data.ByteString as BS |
| 11 | +import qualified Data.ByteString.Lazy as BS |
11 | 12 |
|
12 | 13 | import Control.Monad.Reader
|
13 | 14 | import Control.Monad.Except
|
14 | 15 |
|
15 | 16 | import Options.Applicative
|
16 | 17 |
|
| 18 | +import Lichen.Util |
17 | 19 | import Lichen.Error
|
18 | 20 | import Lichen.Config
|
19 | 21 | import Lichen.Config.Languages
|
20 | 22 | import Lichen.Config.Count
|
21 |
| -import qualified Lichen.Parser as P |
22 |
| - |
23 |
| -countToken :: Language -> String -> FilePath -> Erring Integer |
24 |
| -countToken (Language _ l _ readTok _) t p = do |
25 |
| - src <- liftIO $ BS.readFile p |
26 |
| - tokens <- l p src |
27 |
| - return . fromIntegral . length . filter (hash (readTok t) ==) . fmap hash $ tokens |
28 |
| - |
29 |
| -countNode :: Language -> String -> FilePath -> Erring Integer |
30 |
| -countNode l t p = do |
31 |
| - src <- liftIO $ BS.readFile p |
32 |
| - tree <- parser l p src |
33 |
| - return $ P.countTag (T.pack t) tree |
34 |
| - |
35 |
| -countCall :: Language -> String -> FilePath -> Erring Integer |
36 |
| -countCall l t p = do |
37 |
| - src <- liftIO $ BS.readFile p |
38 |
| - tree <- parser l p src |
39 |
| - return $ P.countCall (T.pack t) tree |
40 |
| - |
41 |
| -dispatchCount :: String -> Language -> String -> FilePath -> Erring Integer |
42 |
| -dispatchCount "token" = countToken |
43 |
| -dispatchCount "node" = countNode |
44 |
| -dispatchCount "call" = countCall |
45 |
| -dispatchCount "function" = countCall |
46 |
| -dispatchCount _ = counterDummy |
| 23 | +import Lichen.Count.Counters |
47 | 24 |
|
48 | 25 | parseOptions :: Config -> Parser Config
|
49 | 26 | parseOptions dc = Config
|
50 |
| - <$> (languageChoice (language dc) <$> (optional . strOption $ long "language" <> short 'l' <> metavar "LANG" <> help "Language of student code")) |
51 |
| - <*> fmap dispatchCount (argument str (metavar "COUNTER")) |
| 27 | + <$> strOption (long "data-dir" <> short 'd' <> metavar "DIR" <> showDefault <> value (dataDir dc) <> help "Directory to store internal data") |
| 28 | + <*> (languageChoice (language dc) <$> (optional . strOption $ long "language" <> short 'l' <> metavar "LANG" <> help "Language of student code")) |
| 29 | + <*> (counterChoice (counter dc) <$> (optional . strOption $ long "counter" <> short 'c' <> metavar "COUNTER" <> help "Counting method")) |
52 | 30 | <*> optional (argument str (metavar "ELEMENT"))
|
53 | 31 | <*> many (argument str (metavar "SOURCE"))
|
54 | 32 |
|
55 | 33 | realMain :: Config -> IO ()
|
56 |
| -realMain c = do |
57 |
| - options <- liftIO $ execParser opts |
| 34 | +realMain ic = do |
| 35 | + iopts <- liftIO . execParser $ opts ic |
| 36 | + mcsrc <- readSafe BS.readFile Nothing (dataDir iopts </> "config_count.json") |
| 37 | + options <- case mcsrc of Just csrc -> do |
| 38 | + c <- case eitherDecode csrc of Left e -> (printError . JSONDecodingError $ T.pack e) >> pure ic |
| 39 | + Right t -> pure t |
| 40 | + liftIO . execParser $ opts c |
| 41 | + Nothing -> pure iopts |
58 | 42 | flip runConfigured options $ do
|
59 | 43 | config <- ask
|
60 | 44 | t <- case toCount config of Just t -> return t; Nothing -> throwError $ InvocationError "No countable element specified"
|
61 | 45 | ps <- liftIO . mapM canonicalizePath $ sourceFiles config
|
62 |
| - counts <- lift $ mapM (method config (language config) t) ps |
| 46 | + counts <- lift $ mapM (runCounter (counter config) (language config) t) ps |
63 | 47 | liftIO . print $ sum counts
|
64 |
| - where opts = info (helper <*> parseOptions c) (fullDesc <> progDesc "Count occurences of a specific AST node" <> header "lichen-count-node - token counting") |
| 48 | + where opts c = info (helper <*> parseOptions c) (fullDesc <> progDesc "Count occurences of a specific AST node" <> header "lichen-count-node - token counting") |
0 commit comments