1
1
mirror of https://github.com/github/semantic.git synced 2024-12-21 13:51:44 +03:00
semantic/semantic-ast/src/Main.hs
2019-10-16 11:53:32 -04:00

60 lines
1.8 KiB
Haskell

{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE TypeApplications #-}
module Main (main) where
import System.Environment
import TreeSitter.Unmarshal
import TreeSitter.Python.AST
import TreeSitter.Python
import Source.Range
import Source.Span
import Data.ByteString.Char8
import Data.ByteString (pack, readFile, ByteString)
import System.IO (FilePath)
import Options.Applicative hiding (style)
import Data.Semigroup ((<>))
data SemanticAST = SemanticAST
{ format :: Format
, source :: Either FilePath Prelude.String
} deriving (Read)
parseAST :: Parser SemanticAST
parseAST = SemanticAST
<$> option auto
( long "format"
<> help "Specify desired output: show, json, sexpression" )
<*> (Left <$> strOption
( long "sourceFile"
<> metavar "FILEPATH"
<> help "Specify filepath containing source code to parse" )
<|> Right <$> strOption
(long "sourceString"
<> metavar "STRING"
<> help "Specify source input to parse"
))
main :: IO ()
main = generateAST =<< execParser opts
generateAST :: SemanticAST -> IO ()
generateAST (SemanticAST _ source) = do
case source of
Left filePath -> do
bytestring <- Data.ByteString.readFile filePath
print =<< parseByteString @TreeSitter.Python.AST.Module @(Range, Span) tree_sitter_python bytestring
Right source -> do
let bytestring = Data.ByteString.Char8.pack source
print =<< parseByteString @TreeSitter.Python.AST.Module @(Range, Span) tree_sitter_python bytestring
opts :: ParserInfo SemanticAST
opts = info (parseAST <**> helper)
( fullDesc
<> progDesc "Parse source code and produce an AST"
<> header "semantic-ast is a package used to parse source code" )
-- TODO: Define formats for json, sexpression, etc.
data Format = Show
deriving (Read)