module Main where import Control.Concurrent import Control.Concurrent.STM import Control.Monad import Control.Monad.IO.Class import Data.Text.IO as T import System.Environment import System.IO as SIO import Compiler.Parser import UI.Widgets.Common import IDE.IDE import Interpreter import Interpreter.Common data CommandLineOptions = StartIDE FilePath | RunProgram FilePath getCommandLineOption :: IO CommandLineOptions getCommandLineOption = do getArgs >>= \case ["run", filePath] -> pure $ RunProgram filePath [filePath] -> pure $ StartIDE filePath _ -> do error "Unrecognized cmd line arguments. Pass a file name (existing or new) to load the program in the IDE, or using 'spade run filename.spd' command to just run the program without starting the IDE." main :: IO () main = do SIO.hSetEcho stdin False SIO.hSetBuffering stdin NoBuffering SIO.hSetBuffering stdout (BlockBuffering Nothing) vty <- initializeVty inputBroadcastChan <- liftIO newBroadcastTChanIO void $ forkIO $ forever $ do keys' <- readVtyEvent vty mapM (atomically . writeTChan inputBroadcastChan) keys' getCommandLineOption >>= \case RunProgram filePath -> do content <- T.readFile filePath program <- compile content inputChan <- liftIO $ atomically $ dupTChan inputBroadcastChan is <- interpret_ inputChan program tryTakeMVar (isDebugOut is) >>= \case Just (Errored t) -> T.putStrLn t _ -> pure () StartIDE filePath -> runIDE filePath inputBroadcastChan liftIO $ shutdownVty vty