{- Main -- The main source of the Dao program. - Copyright (C) March 6, 2009, Ramin Honary - - The main source of the Dao program. This file contains little more than the main - function, a function to manage input arguments and the environment, and then a - run loop which calls the "readline" library and passes the string input to the Dao - runtime interpreter in the "Dao.hs" source file. - - THIS PROGRAM IS INCOMPLETE AS OF: March 15, 2009 - ------------------------------------------------ - - This program is free software: you can redistribute it and/or modify - it under the terms of the GNU General Public License as published by - the Free Software Foundation, either version 3 of the License, or - (at your option) any later version. - - This program is distributed in the hope that it will be useful, - but WITHOUT ANY WARRANTY; without even the implied warranty of - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the - GNU General Public License for more details. - - You should have received a copy of the GNU General Public License - along with this program. If not, see . - - Licensed under the GNU General Public License -} module Dao where -- import qualified Data.Map as Map -- import qualified Data.Set as Set import System import System.Environment import System.Console.Readline import System.IO -- import System.IO.Error -- import System.Process import Ramins_mod import Errst import Parser_st import Dao_base_parser import Dao_base import Dao ---------1---------2---------3---------4---------5---------6---------7---------8---------9--------10 {- Take an input string from the "readline" library routine, run the "dao" state with that input - string, then loop. If the "dao" state comes back with it's on-off switch set to False, return - control to the main function and (presumably) quit the program. -} run_loop :: Dao -> IO () run_loop dao = do if (onoff_switch dao) then do instr <- readline ">> " case instr of Nothing -> return () (Just instr) -> do dao1 <- apply_string_input instr dao run_loop dao1 else return () manage_args :: [String] -> [(String, String)] -> IO Dao manage_args args env = do return (Dao True args env [Map.empty] Map.empty Map.empty [] [] []) main = do args <- getArgs env <- getEnvironment dao <- manage_args args env run_loop dao