Skip to content

Instantly share code, notes, and snippets.

@isomorphism
Created May 12, 2013 00:55
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save isomorphism/5561968 to your computer and use it in GitHub Desktop.
Save isomorphism/5561968 to your computer and use it in GitHub Desktop.
Comments on code structure and style. My remarks are preceded by a ~ in the comments.
module Map
( RoomId, Connection
, Room(..), Map
, describeRoom
, numberRooms
, generateMap
, Wumpus (..)
) where
-- use a proper key/value lookup data structure instead of lists
import qualified Data.Map as M
-- | Data types
-- ~ Use type synonyms to make it more obvious what type signatures mean.
type RoomId = Int
type Connection = Int
-- ~ Use Data.Map for the exits.
-- ~ Haskell programmers like to line things up in columns. It's an OCD
-- sorta thing, just roll with it.
data Room = Room
{ number :: RoomId
, connections :: [RoomId]
}
-- ~ Derive standard type classes when they make sense. They're handy.
deriving (Eq, Ord, Read, Show)
-- ~ The Show type class really isn't intended for user-friendly output. It's
-- more a serialize-to-String sort of deal.
describeRoom :: Room -> String
describeRoom r = concat
[ "Room number: ", show (number r), ", "
, "Connected rooms: ", show (connections r), "\n"
]
-- ~ The two different meanings of "Map" here is a bit unfortunate... sigh
type Map = M.Map RoomId Room
data Wumpus = Wumpus { wloc :: RoomId, moved :: Int }
-- | Map functions
-- ~ Moving the nested conditionals out to a helper function here helps clarify
-- what's being done.
parseMapSize :: String -> Maybe Int
parseMapSize "small" = Just 6
parseMapSize "medium" = Just 12
parseMapSize "large" = Just 20
parseMapSize _ = Nothing
numberRooms :: IO Int
numberRooms = do
putStrLn "What size would you like your map? "
putStrLn "(small/medium/large)"
line <- getLine
-- ~ "case" is usually nicer than "if", especially when converting input.
-- instead of validating-then-using, process in one go and use Either or
-- Maybe to indicate failure, as below.
case parseMapSize line of
Nothing -> do
putStrLn "Sorry, but that's not a map size! "
numberRooms
Just sz -> return sz
-- ~ Each room is created independently of the others, so that logic can be
-- extracted. The order of arguments was switched because the "half" parameter
-- is more likely to be constant across multiple uses of the function. See
-- below for why this matters.
generateRoom :: Int -> Int -> Room
generateRoom half x
| x == 2 * half = Room x [1, x - half, x - 1]
| x > half = Room x [x - half, x - 1, x + 1]
| x == 1 = Room 1 [2, 1 + half, 2 * half]
| otherwise = Room x [x - 1, x + 1, x + half]
-- ~ It's usually preferred to avoid explicit recursion where possible, and
-- rely on standard library functions. Note the partial application made
-- simpler by the alternate argument order for generateRoom. The resulting
-- list of rooms is then turned into a Data.Map for easier lookup.
generateMap :: Int -> Int -> Map
generateMap x half = M.fromList . zip [1 .. x] $ map (generateRoom half) [1 .. x]
module Player
( Player ( .. )
, promptDirection
, promptMove
, promptShoot
, shootArrow
, describePlayer
, movePlayer
, parseDirection
, checkForWumpus
) where
import Control.Applicative ((<$>))
import Data.Maybe (fromMaybe)
import Data.List (elemIndex)
import Data.Map ((!))
import System.IO
import Map
data Player = Player
-- ~ Store the current room. It contains its own ID anyway and saves
-- unnecessary lookups to find the exits.
{ playerRoom :: Room
-- ~ Store which connection the player entered via. Makes it simpler to
-- compute the relative directions for exits..
, enteredFrom :: Connection
, arrows :: Int
}
deriving (Eq, Ord, Read, Show)
-- ~ See comment in Map.hs about Show
describePlayer :: Player -> String
describePlayer p = concat
[ "Player location: Room ", show (number $ playerRoom p), ", "
, "Entered from direction ", show (enteredFrom p), ", "
, "arrows: ", show (arrows p)
]
-- | Player functions
-- ~ The input functions here were changed to match the structure of
-- numberRooms and use a single shared function to handle looping until
-- valid input. This doesn't immediately work with the way input is handled
-- in Main.hs, which tries to interpret a full command first before falling
-- back to prompting for a direction. The better solution here is a more
-- structured command parser, even if a very simple one, rather than lots of
-- ad hoc conditionals mixed in with IO and the maintenance nightmare that
-- will eventually become.
-- ~ This takes a String prompt
promptDirection prompt = do
putStrLn prompt
line <- getLine
case parseDirection line of
Nothing -> do
putStrLn "Sorry, that is not a direction."
promptDirection prompt
Just c -> return c
promptMove :: Player -> Map -> IO Player
promptMove p m = movePlayer p m
<$> promptDirection "Which direction would you like to move?"
promptShoot :: Player -> Map -> Wumpus -> IO (Player, Bool)
promptShoot p m w = do
c <- promptDirection "Which direction would you like to shoot?"
shootArrow p m w c
-- ~ This function really shouldn't be checking for the Wumpus and doing IO.
-- It's better to consolidate the status checks in few location, do all the
-- IO in or near the main game loop, and leave as much as possible to simple
-- single-purpose functions that calculate some property of an entity or
-- the result of an action.
shootArrow p m w c
| wloc w == number r = return (p, True)
| otherwise = do
putStr $ "You hear the clatter of your arrow in the next room. You have " ++ show (arrows p - 1) ++ " left in your quiver. "
hFlush stdout
return (p { arrows = arrows p - 1 }, False)
where r = roomInDirection p m c
-- ~ The getDirection function did not need to use IO, but it's been split up
-- anyway into smaller functions.
-- ~ Same deal as with the sizes in Map.hs
parseDirection :: String -> Maybe Connection
parseDirection "back" = Just 0
parseDirection "left" = Just 1
parseDirection "right" = Just 2
parseDirection _ = Nothing
-- ~ The connections for each room are room IDs stored in clockwise order. To
-- find a relative exit, then, the chosen connection number can be added to
-- the connection the player entered from and the sum modulo 3 will be the
-- absolute direction.
relativeDirection :: Connection -> Player -> Connection
relativeDirection c p = (enteredFrom p + c) `mod` 3
-- ~ Small, helpful functions like this are usually good.
roomInDirection :: Player -> Map -> Connection -> Room
roomInDirection plr m c = m ! newRoomId
where newRoomId = connections (playerRoom plr) !! relativeDirection c plr
movePlayer :: Player -> Map -> Connection -> Player
movePlayer plr m c = plr { playerRoom = newRoom, enteredFrom = entryDir }
where newRoom = roomInDirection plr m c
-- ~ This is kind of a hack, but I didn't feel like adding the extra
-- error handling to recover from an invalid map. So if you generate
-- a map where room connections are one-way things will get weird
-- instead of it just crashing.
entryDir = fromMaybe 0 $ elemIndex (number $ playerRoom plr) (connections room)
-- ~ This function did not need to use IO.
-- ~ Using guards is usually nicer than a function having nested conditionals
-- as its entire body.
-- ~ Returning magic numbers to indicate a result is a bad practice in general.
-- I didn't change that here, but it's something you should consider (if you
-- feel like improving things further).
checkForWumpus :: Player -> Wumpus -> Int
checkForWumpus p w
| wloc w `elem` connections (playerRoom p) = 0
| wloc w == number (playerRoom p) = if moved w == 0 then 1 else 2
| otherwise = 3
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment