Skip to content

Instantly share code, notes, and snippets.

@cipharius
Created September 10, 2020 08:36
Show Gist options
  • Save cipharius/4cec61262788c8c878b53aae1a5cdefd to your computer and use it in GitHub Desktop.
Save cipharius/4cec61262788c8c878b53aae1a5cdefd to your computer and use it in GitHub Desktop.
Simple revers polish notation parser and calculator in Haskell
{-# LANGUAGE OverloadedStrings #-}
import qualified Data.Text as T
import Data.Attoparsec.Text
data Op
= Add Op Op
| Sub Op Op
| Mul Op Op
| Div Op Op
| Const Double
deriving Show
calc :: Op -> Maybe Double
calc (Const x) = Just $ x
calc (Add x y) = (+) <$> (calc x) <*> (calc y)
calc (Sub x y) = (-) <$> (calc x) <*> (calc y)
calc (Mul x y) = (*) <$> (calc x) <*> (calc y)
calc (Div x y) = (/) <$> (calc x) <*> (nonZero =<< calc y)
where
nonZero 0 = Nothing
nonZero r = Just r
opParser :: Parser Op
opParser = choice
[ operatorP <* skipSpace <*> opParser <* skipSpace <*> opParser
, Const <$> double
]
where
operatorP = choice
[ char '+' *> pure Add
, char '-' *> pure Sub
, char '*' *> pure Mul
, char '/' *> pure Div
]
main :: IO ()
main = getLine >>= putStrLn . calculate . parseText . T.pack
where
parseText = parseOnly (opParser <* endOfInput)
calculate (Left err) = "Parse error: " <> err
calculate (Right ast) = maybe "NaN" show (calc ast)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment