rubyhs/src/Rubyhs.hs

88 lines
2.6 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_)
2019-10-16 19:51:47 +00:00
import Data.Map (Map)
import Data.Set (Set)
2019-10-16 18:33:15 +00:00
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
2019-10-16 19:51:47 +00:00
import qualified Data.Graphviz as Graphviz
import qualified Data.Language.Ruby as Ruby
import qualified Data.Text.IO as Text
2019-10-16 18:33:15 +00:00
import qualified Options.Applicative as Options
2019-10-17 18:08:25 +00:00
import qualified Rubyhs.References as Ruby
2019-09-26 21:45:14 +00:00
main :: IO ()
2019-10-14 19:46:02 +00:00
main = do
2019-10-16 19:57:12 +00:00
Command{targets, printAST, maybeDotPath} <- getCommand
2019-10-17 18:08:25 +00:00
blocks <- parseInput @Ruby.Begin targets
2019-10-16 19:57:12 +00:00
let
act block = do
2019-10-17 18:08:25 +00:00
let res@(Ruby.Result x) = Ruby.references $ block
2019-10-16 19:57:12 +00:00
putEncoded res
2019-10-17 18:08:25 +00:00
ByteString.putStrLn . Aeson.encode . toJSONForest . Ruby.graph $ block
2019-10-16 19:57:12 +00:00
case maybeDotPath of
Nothing -> pure ()
Just dotPath -> drawDot dotPath x
2019-10-14 19:46:02 +00:00
if printAST
then traverse_ @[] putEncoded blocks
2019-10-16 19:51:47 +00:00
else traverse_ act blocks
2019-10-17 18:08:25 +00:00
drawDot :: FilePath -> Map Ruby.Node (Set Ruby.Node) -> IO ()
2019-10-16 19:57:12 +00:00
drawDot p
= Text.writeFile p
2019-10-16 19:51:47 +00:00
. Graphviz.digraph
2019-10-17 18:08:25 +00:00
. fmap (fmap (qoutes . Ruby.prettyContext) . \(x, xs) -> x :| toList xs)
2019-10-16 19:51:47 +00:00
. toList
qoutes :: Text -> Text
qoutes x = "\"" <> x <> "\""
2019-10-16 18:12:07 +00:00
2019-10-17 18:08:25 +00:00
toJSONForest :: Forest Ruby.Node -> Aeson.Value
2019-10-16 18:12:07 +00:00
toJSONForest = Aeson.Object . fromList . fmap go
where
2019-10-17 18:08:25 +00:00
go (Node x xs) = (Ruby.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
2019-10-16 19:57:12 +00:00
{ targets :: [FilePath]
, printAST :: Bool
, maybeDotPath :: Maybe FilePath
2019-10-14 19:46:02 +00:00
}
command :: Parser Command
2019-10-16 19:57:12 +00:00
command = Command <$> targets <*> printAST <*> dotPath
2019-10-14 19:46:02 +00:00
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-16 19:57:12 +00:00
dotPath
= Options.optional
$ Options.strOption
$ Options.long "dot"
<> Options.metavar "PATH"
<> Options.help "Write dot graph"
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" )