[Haskell-cafe] Haskell Pangolins
Derek Elkins
ddarius at hotpop.com
Thu Dec 30 00:05:58 EST 2004
I've rewritten it closer to the way I would have written it. Most of the changes
are minor syntactic changes that you may or may not agree with. Probably the most
confusing part of the original code was the declaration of the Node datatype as
a (sum of) record(s), then the subsequent ignoring of the fact that it is a record.
In my experience, most Haskell programmer's would not (for better or worse) use a
record in this case. The comments I've added are with regards to the original
source code; compare this version and yours to see the differences. As far as
how the code actually works, it seems to be the most natural implementation.
-- Pangolins in Haskell
-- A simple animal guessing game
module Main ( main ) where
import Control.Monad ( liftM )
-- declared as record, but not used as record
data Node
= Guess String
| Question String Node Node
-- putStrLn s == putStr s >> putStr "\n"
ask question = do
putStrLn question
getLine -- m >>= return == m (one of the monad laws)
isYes "y" = True
isYes "yes" = True
isYes "Y" = True
isYes "YES" = True
isYes _ = False
withArticle fullstring@(c:cs)
| c `elem` "aeiou" = "an " ++ fullstring
| otherwise = "a" ++ fullstring
rewrite (Guess name) = do
reply <- ask ("Is it " ++ withArticle name ++ "?") -- superfluous parens
if isYes reply -- superfluous parens
then do
putStr "Computer wins!\n"
return (Guess name)
else do
newName <- ask "What is it, then?"
newQuestion <- newQuestion name newName
return newQuestion
rewrite (Question text ifYes ifNo) = do
reply <- ask text
if isYes reply
then liftM (flip (Question text) ifNo) (rewrite ifYes)
else liftM (Question text ifYes) (rewrite ifNo)
newQuestion a1 a2 = do -- superfluous parens
text <- ask ("Tell me a question that can be used to distinguish between " ++ withArticle a1 ++ " and " ++ withArticle a2 ++ ".")
answer <- ask ("What would the answer to your question be if it was " ++ withArticle a1 ++ "?")
if isYes answer -- superfluous parens
then return (Question text (Guess a1) (Guess a2))
else return (Question text (Guess a2) (Guess a1))
-- superfluous parens
duck = Guess "duck"
dog = Guess "dog"
initialNode = Question "Does it quack?" duck dog
-- superfluous 'do'
main = play initialNode
play :: Node -> IO ()
play node = do
rewrittenNode <- rewrite node
playAgain <- ask "Play again?"
if not (isYes playAgain) then putStrLn "Goodbye for now." -- superfluous 'do'
else play rewrittenNode -- superfluous 'do'
More information about the Haskell-Cafe
mailing list