2019-09-27 16:32:01 +00:00
|
|
|
{-# LANGUAGE DuplicateRecordFields, OverloadedLists #-}
|
|
|
|
{-# OPTIONS_GHC -Wall #-}
|
|
|
|
module Data.Language.Ruby
|
2019-10-16 18:14:48 +00:00
|
|
|
( module Data.Language.Ruby.AST
|
2019-10-16 18:33:15 +00:00
|
|
|
, parse
|
|
|
|
, parseFile
|
2019-09-27 16:32:01 +00:00
|
|
|
) where
|
|
|
|
|
2019-10-16 18:33:15 +00:00
|
|
|
import Data.Aeson (eitherDecode)
|
|
|
|
import Data.ByteString.Lazy (ByteString)
|
2019-10-16 18:14:48 +00:00
|
|
|
import Data.Language.Ruby.AST
|
2019-10-16 18:33:15 +00:00
|
|
|
import Frelude
|
|
|
|
import System.IO (hFlush)
|
|
|
|
import System.IO.Temp (withSystemTempFile)
|
|
|
|
import System.Process (readProcess)
|
|
|
|
import qualified Data.ByteString.Lazy.Char8 as ByteString
|
|
|
|
|
|
|
|
decodeFail :: MonadFail m => FromJSON a => ByteString -> m a
|
|
|
|
decodeFail s = case eitherDecode s of
|
|
|
|
Left err -> Frelude.fail err
|
|
|
|
Right a -> pure a
|
|
|
|
|
|
|
|
runRubyParseFile :: FilePath -> IO String
|
|
|
|
runRubyParseFile p = sh "ruby-parse" ["--emit-json", "--25", p]
|
|
|
|
|
|
|
|
runRubyParse :: ByteString -> IO String
|
|
|
|
runRubyParse s = withSystemTempFile "rubyhs" $ \p h -> do
|
|
|
|
ByteString.hPut h s
|
|
|
|
hFlush h
|
|
|
|
runRubyParseFile p
|
|
|
|
|
|
|
|
sh :: String -> [String] -> IO String
|
|
|
|
sh cmd a = readProcess cmd a mempty
|
|
|
|
|
|
|
|
parseFile :: FromJSON a => FilePath -> IO a
|
|
|
|
parseFile = runRubyParseFile >=> decodeFail . ByteString.pack
|
|
|
|
|
|
|
|
parse :: FromJSON a => ByteString -> IO a
|
|
|
|
parse = runRubyParse >=> decodeFail . ByteString.pack
|