{-# LANGUAGE ViewPatterns #-} import Data.List import Text.Read import Control.Monad main :: IO () main = io (show . rpn) io :: (String -> String) -> IO () io f = interact (unlines . map f . filter (not . null) . lines) rpn :: String -> Either String Double rpn = foldM parse [] . words >=> return . head parse :: [Double] -> String -> Either String [Double] parse (y:x:xs) (flip lookup dyad -> Just f) = Right (f x y : xs) parse (x:xs) (flip lookup monad -> Just f) = Right (f x : xs) parse xs (flip lookup nilad -> Just k) = Right (k : xs) parse xs x = case readMaybe x of Just x -> Right (x : xs) Nothing -> Left "Syntax error" -- dyadic functions dyad = [ ("+", (+)) , ("-", (-)) , ("*", (*)) , ("/", (/)) , ("^", (**)) ] -- monadic functions monad = [ ("sin" , sin ) , ("asin" , asin) , ("cos" , cos ) , ("acos" , acos) , ("tan" , tan ) , ("atan" , atan) , ("ln" , log ) , ("sqrt" , sqrt) , ("sgn" , signum) , ("abs" , abs) , ("floor", fromIntegral . floor) , ("ceil" , fromIntegral . ceiling) ] -- niladic functions nilad = [ ("pi" , pi) , ("e" , exp 1) , ("phi", (1 + sqrt 5)/2) ]