{-# LANGUAGE DuplicateRecordFields, OverloadedLists #-} {-# OPTIONS_GHC -Wall #-} module Data.Language.Ruby ( module Data.Language.Ruby.AST , parse , parseFile ) where import Data.Aeson (eitherDecode) import Data.ByteString.Lazy (ByteString) import Data.Language.Ruby.AST 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