Skip to content

Commit

Permalink
variable replacement in equations
Browse files Browse the repository at this point in the history
  • Loading branch information
AidanV committed Jun 29, 2024
1 parent 26d4498 commit b96edb9
Show file tree
Hide file tree
Showing 3 changed files with 20 additions and 2 deletions.
2 changes: 1 addition & 1 deletion app/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -68,7 +68,7 @@ appEvent (T.VtyEvent (V.EvKey V.KBackTab [])) =
focusRing %= F.focusPrev
appEvent (T.VtyEvent (V.EvKey V.KEnter [])) = do
s <- T.get
let ans = show $ calculate $ unlines $ E.getEditContents $ s ^. editEquation
let ans = show $ calculateWithVar (s ^. previousAnswers) $ unlines $ E.getEditContents $ s ^. editEquation
T.put $
St
(F.focusRing [EditEquation])
Expand Down
14 changes: 14 additions & 0 deletions lib/Calc.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,19 @@
module Calc where

calculateWithVar :: [String] -> String -> Double
calculateWithVar prevAns eq =
let variables = zip ['a' ..] prevAns
replacedString = foldl (\acc (c, prevAns) -> replaceCharWithString c prevAns acc) eq variables
in calculate replacedString

replaceCharWithString :: Char -> String -> String -> String
replaceCharWithString c replacement [] =
[]
replaceCharWithString c replacement (firstChar : rest) =
if firstChar == c
then replacement ++ replaceCharWithString c replacement rest
else firstChar : replaceCharWithString c replacement rest

-- TODO: Figure out why Num does not work
calculate :: String -> Double -- (Num a, Read a, Show a) => String -> a
calculate =
Expand Down
6 changes: 5 additions & 1 deletion tests/BackendTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -25,6 +25,9 @@ testNaturalLog = TestCase (assertEqual "Calculating: 2.718281828459045 ln" 1.0 $
testSqrt :: Test
testSqrt = TestCase (assertEqual "Calculating: 16 sqrt" 4.0 $ calculate "16 sqrt")

testAdditionWithVar :: Test
testAdditionWithVar = TestCase (assertEqual "Calculating: 1 a + where a = 10" 11.0 $ calculateWithVar ["10.0"] "1 a +")

tests :: Test
tests =
TestList
Expand All @@ -34,7 +37,8 @@ tests =
TestLabel "Test Division" testDivision,
TestLabel "Test Exponentiation" testExponentiation,
TestLabel "Test Natual Log" testNaturalLog,
TestLabel "Test Sqrt" testSqrt
TestLabel "Test Sqrt" testSqrt,
TestLabel "Test Addition w/ Var" testAdditionWithVar
]

main :: IO ()
Expand Down

0 comments on commit b96edb9

Please sign in to comment.