{-# OPTIONS_GHC -fno-warn-type-defaults #-} {- | Module : $Header$ Description: IO Operations for clac. Copyright : (c) Alexander Berntsen 2015 License : GPL-3 Maintainer : alexander@plaimi.net -} module Clac.IO where import Control.Applicative ( (<$>), ) import Control.Monad ( when, ) import Data.List.Split ( splitOn, ) import Data.Maybe ( mapMaybe, ) import System.IO ( hFlush, stdout, ) import Plailude import Clac.CliParser ( Opt, e, h, r, v, ) import Clac.REPL ( inlet, repAns, repLets, unlet, ) import Clac.Stack ( os, sa, ) f :: Show a => Opt -> [(a, String)] -> IO () -- | Formats an answer and optionally (if the verbose option is set) its -- answer tree for printing. Puts '='s under the answer. f o = mapM_ (\(solution, tree) -> do when (v o) $ putStrLn $ "\n\n" ++ tree print solution putStrLn $ replicate (length $ show solution) '=') repl :: (Floating a, Real a, Read a, Show a) => Opt -> [(String, String)] -> [a] -> IO b -- | Run a REPL (Read-Evaluate-Print-Loop). -- -- Prompts the user for input, solves it with 'sa' after checking if there -- were multiple equations per the 'Neq' operator, and prints it using 'f'. -- Prints an answer tree if the verbose option is activated. -- -- > 1 1 + , 2 2 + -- this is turned into [["1","1","+"],["2","2","+"]] -- -- There is a let stack. The user may add things to the let stack with #let. -- The stack may be printed with #lets. Variables may also be unlet with -- #unlet and #unletall. -- -- > #let a = 1 -- the let stack is now [("a", "1")], i.e. a bound to 1 -- > #let b = 2 -- the let stack is now [("b","2"),("a","1")] -- > #let c = 3 -- the let stack is now [("c","3"),("b","2"),("a","1")] -- > #lets -- prints [("c","3"),("b","2"),("a","1")] -- > #unlet a -- the let stack is now [("c","3"),("b","2")] -- > #unletall -- the stack is now empty -- -- 'repl' runs 'repLets' to reduce an application of a variable bound by let -- with its value. -- -- > #let a = 1 -- > a a + -- this is turned into [["1","1","+"]] -- -- There is an ans stack. Every answer is added to this automatically. The ans -- function lets the user use these answers. #ans prints the stack. -- -- > 1 -- ans stack is now [1.0] -- > 0 ans -- this is turned into [["1"]] -- > #ans -- prints [1.0] repl o lets ans = do putStr ">" hFlush stdout l <- words <$> getLine case l of ("#ans":_) -> print ans >> repl o lets ans ("#lets":_) -> print lets >> repl o lets ans ["#let", x, "=", y] -> repl o (inlet x y lets) ans ["#unlet", x] -> repl o (unlet x lets) ans ("#unletall":_) -> repl o [] ans _ -> do let ss = sa . splitOn [","] . repAns ans . repLets lets $ l f o ss repl o lets (mapMaybe fst ss ++ ans) clac :: Opt -> [[String]] -> IO () -- | Run the calculator. -- -- If an equation is given as an argument to the program, it is solved with -- 'sa', and formatted and printed by 'f'. -- -- > $ clac 1 1 + -- > Just 2.0 -- > ======== -- -- If there is STDIN waiting, 'clac' calls itself with the equation in STDIN -- as an argument. -- -- > $ echo 1 1 + | clac -- > Just 2.0 -- > ======== -- -- If there is there is nothing to solve, it starts the REPL with 'repl'. -- -- > $ clac -- > > -- -- The REPL should be started with GNU rlwrap or similar software for an -- optimal experience. -- -- > $ rlwrap clac -- > > clac o [[]] = repl o [] [] ~+~ (getContents >>= \cs -> clac o (splitOn [","] . words $ cs)) clac o es = f o . sa $ es calc :: Opt -> IO () -- | Check what flags the user has given, if any, and run the program -- accordingly. Prints various help output, or runs the calculator with -- 'clac'. calc o | h o = mapM_ putStrLn $ "OPERATORS":"=========":map snd os | r o = mapM_ putStrLn ["REPL OPERATIONS","===============" ,"#lets:\tprint the let stack" ,"#unletall:\tempty the let stack" ,"#let:\t#'let a = b', bind a to b" ,"#unlet:\t'#unlet v', remove the let binding v" ,"#ans:\tprint the answer stack" ,"ans:\tanswer operator, use the n-th last ans" ] | otherwise = clac o $ splitOn [","] $ case e o of [a] -> words a _ -> e o