[Haskell-beginners] newbie seeking code review
Sean Perry
shaleh at speakeasy.net
Thu Apr 28 09:26:41 CEST 2011
I just finished "Learn you a Haskell". Fine book, really enjoyed it. Early on he develops a very simple RPN evaluator. I played with it a bit and expanded it to use Either instead of Maybe.
Also, '_' recalls the last value so you can do:
> 10 5 +
15.0
> _ 3 *
45.0
> _ 5 /
9.0
This is one of my first complete pieces of Haskell. I would appreciate comments on style, formatting, etc. There are comments in places I am seeking particular guidance.
If you are also reading along in LYAH, warning spoiler alert......
import Control.Monad (foldM, liftM)
import Control.Monad.Error
import System.Exit (exitFailure, exitSuccess)
import System.IO (hFlush, stdout)
import System.IO.Error (isEOFError)
readNumMaybe :: String -> Either String Double
readNumMaybe st = case reads st of [(x, "")] -> Right x
[(x, s)] -> Left $ "incomplete parse: '" ++ st ++ "'"
[] -> Left $ "unknown value: '" ++ st ++ "'"
evalRPN :: [Double] -> String -> Either String [Double]
evalRPN _ "clear" = return []
evalRPN (x:y:xs) "+" = return $ (y + x):xs
evalRPN (x:y:xs) "-" = return $ (y - x):xs
evalRPN (x:y:xs) "*" = return $ (y * x):xs
evalRPN (x:y:xs) "/" = return $ (y / x):xs
evalRPN (x:y:xs) "^" = return $ (y ** x):xs
evalRPN (x:xs) "ln" = return $ (log x):xs
evalRPN xs "sum" = return $ [sum xs]
evalRPN xs num = liftM (:xs) (readNumMaybe num)
evalRPNTokens :: [String] -> Either ([String], String) (Maybe Double)
evalRPNTokens tokens =
case foldM evalRPN [] tokens of
Right [] -> Right Nothing
Right [x] -> Right (Just x)
Right result -> Left $ (tokens, show (length tokens) ++ " items left on stack.")
Left msg -> Left (tokens, msg)
-- is this used with map ok or am I missing a standard function?
replaceif p new s = if s == p then new else s
showEval :: String -> Either ([String], String) (Maybe Double) -> IO String
showEval _ (Right Nothing) = return ""
showEval _ (Right (Just result)) = do -- show result then use this value for the next iteration
print result
return $ show result
showEval last (Left (input, msg)) = do putStrLn $ "Error: '" ++ unwords input ++ "': " ++ msg
-- do not let errors eat the last successful value
return last
getLineOrQuit = catch getLine (\e -> if isEOFError e then putStr "\n" >> exitSuccess else exitFailure)
prompt = "> "
evalLoop :: String -> IO ()
evalLoop last =
do
putStr prompt
hFlush stdout -- ensure the prompt is shown
-- is this too "cute"??
result <- getLineOrQuit >>= showEval last . evalRPNTokens . map (replaceif "_" last) . words
evalLoop result
main = evalLoop ""
More information about the Beginners
mailing list