{-# OPTIONS_GHC -fno-warn-type-defaults #-} {- | Module : $Header$ Description: Functions for clac's Read-Evaluate-Print-Loop. Copyright : (c) Alexander Berntsen 2015 License : GPL-3 Maintainer : alexander@plaimi.net -} module Clac.REPL where import Safe ( readMay, ) import Plailude inlet :: Eq a => a -> b -> [(a, b)] -> [(a, b)] -- | Insert a let into the given stack of lets. If the variable is already -- bound, update it by 'unlet'ing it first, and then let it. -- -- > #let a = 1 -- stack is [("a","1")], i.e. a bound to 1 -- > #let a = 2 -- stack is [("a","2")] inlet k n ls = case lookup k ls of Just _ -> (k, n) : unlet k ls Nothing -> (k, n) : ls unlet :: Eq a => a -> [(a, b)] -> [(a, b)] -- | Remove a let binding from the given stack of lets. Noop if there's -- nothing to unlet. -- -- > #let a = 1 -- stack is [("a", "1")], i.e. a bound to 1 -- > #let b = 2 -- stack is [("b","2"),("a", "1")] -- > #unlet a -- stack is [("b","2")] unlet k = go [] where go u [] = u go u (l@(m,_):ls) | m == k = u ++ ls | otherwise = go (u ++ [l]) ls repLets :: Eq a => [(a, a)] -> [a] -> [a] -- | Matches the passed in let bindings with the passed in equation, and -- reduces any found bindings with their value. -- -- > #let a = 1 -- > a a + -- this is turned into [["1","1","+"]] repLets lets = go [] where go as [] = as go as (l:bs) = case lookup l lets of Just m -> go (as ++ [m]) bs Nothing -> go (as ++ [l]) bs get :: Show a => [a] -> String -> String -- | Used the passed in 'String' as an Integer index into the passed in stack -- of answers. Breaks the equation if the string can't be parsed. -- -- > 0 -- stack is now [0.0] -- > 0 ans -- gets 0.0 from the stack -- > 3 ans -- stack is now [0.0,0.0], no 3rd element -- broken equation get as i = maybe "bork" show $ ((as !?) . floor) =<< readMay i repAns :: Show a => [a] -> [String] -> [String] -- | Matches the passed in ans stack with the passed in equation, and -- reduces any found applications of the ans function with the value -- -- > 1 -- ans stack is now [1.0] -- > 0 ans -- this is turned into [["1"]] repAns ans = go [] where go as [] = as go as (n:m:bs) | m == "ans" = go [] (as ++ (ans `get` n) : bs) | otherwise = go (as ++ [n] ++ [m]) bs go as [a] = as ++ [a]