rubyhs/src/Rubyhs.hs

62 lines
2 KiB
Haskell
Raw Normal View History

2019-09-26 21:45:14 +00:00
{-# LANGUAGE DuplicateRecordFields, OverloadedLists #-}
{-# OPTIONS_GHC -Wall #-}
module Rubyhs (main) where
2019-09-27 16:32:01 +00:00
import Data.Foldable (traverse_)
import Data.Language.Ruby (Block)
2019-10-16 18:33:15 +00:00
import qualified Data.Language.Ruby as Ruby
import Data.Tree (Tree(Node), Forest)
2019-09-27 16:32:01 +00:00
import Frelude
2019-10-14 19:46:02 +00:00
import Options.Applicative (Parser)
2019-10-16 18:12:07 +00:00
import qualified Data.Aeson as Aeson
2019-10-16 18:33:15 +00:00
import qualified Data.ByteString.Lazy.Char8 as ByteString
import qualified Options.Applicative as Options
import qualified Rubyhs.References
2019-09-26 21:45:14 +00:00
main :: IO ()
2019-10-14 19:46:02 +00:00
main = do
Command{targets, printAST} <- getCommand
2019-10-16 18:33:15 +00:00
blocks <- parseInput @Block targets
2019-10-14 19:46:02 +00:00
if printAST
then traverse_ @[] putEncoded blocks
2019-10-16 18:12:07 +00:00
else do
traverse_ (putEncoded . Rubyhs.References.references) blocks
2019-10-16 18:33:15 +00:00
traverse_ (ByteString.putStrLn . Aeson.encode . toJSONForest . Rubyhs.References.graph) blocks
2019-10-16 18:12:07 +00:00
toJSONForest :: Forest Rubyhs.References.Node -> Aeson.Value
toJSONForest = Aeson.Object . fromList . fmap go
where
go (Node x xs) = (Rubyhs.References.prettyContext x, toJSONForest xs)
2019-09-26 21:45:14 +00:00
2019-10-16 18:33:15 +00:00
-- | If arguments is non-empty treat all arguments as filepaths and
-- parse the modules at those locations. If there are no arguments,
-- parse from stdin.
parseInput :: FromJSON a => [FilePath] -> IO [a]
parseInput = \case
[] -> ByteString.getContents >>= fmap pure . Ruby.parse
ps -> traverse Ruby.parseFile ps
2019-10-14 19:46:02 +00:00
putEncoded :: ToJSON a => a -> IO ()
2019-10-16 18:33:15 +00:00
putEncoded = ByteString.putStrLn . Aeson.encode
2019-10-14 19:46:02 +00:00
data Command = Command
{ targets :: [FilePath]
, printAST :: Bool
}
command :: Parser Command
command = Command <$> targets <*> printAST
where
targets = many (Options.argument Options.str (Options.metavar "TARGET"))
printAST = Options.switch
2019-10-14 20:33:13 +00:00
$ Options.long "print-ast"
<> Options.help "Print AST and exit"
2019-10-14 19:46:02 +00:00
getCommand :: IO Command
getCommand = Options.execParser opts
where
opts = Options.info (Options.helper <*> command)
( Options.fullDesc
2019-10-14 20:33:13 +00:00
<> Options.progDesc "Static analysis of Ruby"
<> Options.header "rubyhs - Static analysis of Ruby" )