module Main where import UHC.Light.Compiler.EHC.Main.Utils import qualified UHC.Light.Compiler.Config as Cfg import UHC.Light.Compiler.Base.API import UHC.Light.Compiler.CoreRun.API import UHC.Light.Compiler.Opts import UHC.Util.Pretty import UHC.Util.FPath import System.Exit import System.Console.GetOpt import System.IO import Control.Monad import System.Environment import Data.List import qualified Data.ByteString.Char8 as B {-# LINE 31 "src/ehc/EHCRun.chs" #-} -- | Top level main. TBD: hooks & customization main :: IO () main = do args <- getArgs progName <- getProgName let opts0 = defaultEHCOpts {ehcProgName = mkFPath progName} oo@(o,n,errs) = ehcrunCmdLineOptsApply args opts0 opts = maybe opts0 id o case ehcOptImmQuit opts of Just immq -> handleImmQuitOption ehcrunCmdLineOpts ["rcr"] immq opts _ -> case (n,errs) of ([fname], []) -> run opts fname (_ , es) -> do putStr (head errs) exitFailure where run opts fname = do inp <- B.readFile fname case parseModFromString $ B.unpack inp of Left es -> forM_ es putStrLn Right mod -> do res <- runCoreRunIO opts mod case res of Left e -> putStrLn $ show $ pp e Right val -> putStrLn $ show $ pp val {- _ -> putStrLn $ "Usage: " ++ progName ++ " file.rcr" -}