170 likes | 287 Views
Chapter 19. An Imperative Robot Language. Motivation. In the previous chapter, monads were introduced. In particular, state monads were described as a way to sequence stateful operations such as found in an imperative language.
E N D
Chapter 19 An Imperative Robot Language
Motivation • In the previous chapter, monads were introduced. • In particular, state monads were described as a way to sequence stateful operations such as found in an imperative language. • In this chapter, an imperative DSL called Imperative Robot Language, or IRL, will be designed and implemented. • The implementation will be in the form of a graphical simulator of the robot in action.
IRL Commands • The commands’ behaviors can be guessed from their names and types:move :: Robot () turnRight, turnLeft :: Robot () turnTo :: Direction -> Robot () direction :: Robot Direction blocked :: Robot Bool penUp, penDown :: Robot () setPenColor :: Color -> Robot () pickCoin, dropCoin :: Robot () onCoin :: Robot Bool coins :: Robot Int cond :: Robot Bool -> Robot a -> Robot a -> Robot a while :: Robot Bool -> Robot () -> Robot () (||*), (&&*) :: Robot Bool -> Robot Bool -> Robot Bool (>*), (<*) :: Robot Int -> Robot Int -> Robot Bool isnt :: Robot Bool -> Robot Bool motion pen treasure control
Example: Spiral Motion spiral :: Robot () spiral = penDown >> loop 1 where loop n = let twice = do turnRight moven n turnRight moven n in cond blocked (twice >> turnRight >> moven n) (twice >> loop (n+1)) moven :: Int -> Robot () moven n = mapM_ (const move) [1..n]
Implementing IRL • First we need to define the robot state:data RobotState = RobotState { position :: Position , facing :: Direction , pen :: Bool , color :: Color , treasure :: [ Position ] , pocket :: Int } deriving Showtype Position = (Int, Int) -- a griddata Direction = North | East | South | West deriving (Eq, Show, Enum) • The grid itself is also part of the overall state, but it never changes, and thus is kept separate.
Combining Monads • The most obvious design would be: newtype Robot a = Robot (RobotState -> Grid -> (RobotState, a)) • However, we want the output to also include graphics, so a better design is: newtype Robot a = Robot (RobotState -> Grid -> Window -> IO (RobotState, a)) • In this way the Robot monad and the IO monad are combined.
“Robot” is a State Monad • The instance declaration resembles that of a state monad:instance Monad Robot where return a = Robot $ \s _ _ -> return (s, a) Robot sf0 >>= f = Robot $ \s0 g w -> do (s1, a1) <- sf0 s0 g w let Robot sf1 = f a1 (s2, a2) <- sf1 s1 g w return (s2, a2) • All that remains is defining the “domain specific” operations in the Robot monad.
Helper Functions • For help computing directions:right,left :: Direction -> Direction right d = toEnum (succ (fromEnum d) `mod` 4) left d = toEnum (pred (fromEnum d) `mod` 4) • For help querying and updating the state:updateState :: (RobotState -> RobotState) -> Robot () updateState u = Robot (\s _ _ -> return (u s, ())) queryState :: (RobotState -> a) -> Robot a queryState q = Robot (\s _ _ -> return (s, q s)) • To be defined later:at :: Grid -> Position -> [Direction]“g `at` p” is the list of directions in which the robot can move (i.e. unblocked) from position p.
Directions and Blocking turnLeft :: Robot () turnLeft = updateState ( \s -> s {facing = left (facing s)} )turnRight :: Robot () turnRight = updateState ( \s -> s {facing = right (facing s)} )turnTo :: Direction -> Robot () turnTo d = updateState ( \s -> s {facing = d} )direction :: Robot Direction direction = queryState facingblocked :: Robot Bool blocked = Robot $ \s g _ -> return ( s, facing s `notElem` (g `at` position s) )
Robot Movement move :: Robot ()move = cond1 (isnt blocked) (Robot $ \s _ w -> do let newPos = movePos (position s) (facing s) graphicsMove w s newPos return (s {position = newPos}, ()) )movePos :: Position -> Direction -> PositionmovePos (x,y) d = case d of North -> (x, y+1) South -> (x, y-1) East -> (x+1, y) West -> (x-1, y) • The “graphicsMove” command is defined in Section 19.5 of the text.
Pens and Coins penUp :: Robot ()penUp = updateState (\s -> s {pen = False})penDown :: Robot ()penDown = updateState (\s -> s {pen = True})setPenColor :: Color -> Robot ()setPenColor c = updateState (\s -> s {color = c})onCoin :: Robot BoolonCoin = queryState (\s -> position s `elem` treasure s)coins :: Robot Intcoins = queryState pocketpickCoin :: Robot ()pickCoin = cond1 onCoin (Robot $ \s _ w -> do eraseCoin w (position s) return (s {treasure = position s `delete` treasure s, pocket = pocket s + 1}, () ) )
Lifting to Monads • Functions can be “lifted” to the levels of monads using these pre-defined functions in the Monad library:liftM :: (Monad m) => (a -> b) -> (m a -> m b)liftM f = \a -> do a' <- a return (f a')liftM2 :: (Monad m) => (a -> b -> c) -> (m a -> m b -> m c)liftM2 f = \a b -> do a' <- a b' <- b return (f a' b') • Similarly for liftM3, liftM4, etc.
Logic and Control cond :: Robot Bool -> Robot a -> Robot a -> Robot acond p c a = do pred <- p if pred then c else acond1 p c = cond p c (return ())while :: Robot Bool -> Robot () -> Robot ()while p b = cond1 p (b >> while p b)(||*) :: Robot Bool -> Robot Bool -> Robot Boolb1 ||* b2 = do p <- b1 if p then (return True) else b2isnt :: Robot Bool -> Robot Boolisnt = liftM not(>*), (<*) :: Robot Int -> Robot Int -> Robot Bool(>*) = liftM2 (>)(<*) = liftM2 (<) [ similarly for (&&*) ]
Haskell Arrays • Arrays in Haskell have type: Ix a => Array a bwhere “a” is the index type, and must be in the class Ix, and “b” is the container type, i.e. the type of the values in the array. • Arrays are created by: array :: Ix a => (a, a) -> [(a, b)] -> Array a b • For example: colors :: Array Int Color colors = array (0, 7) (zip [0 .. 7] [Black .. White]) • Arrays are indexed (in constant time) by the (!) operator. For example: colors ! 3 Cyan
The Grid is an Array • The robot grid is a two-dimensional array: type Grid = Array Position [Direction] type Position = (Int, Int) • The list of directions is the unblocked directions in which the robot can move. • In which case the access operator “at” used previously is just: at :: Grid -> Position -> [Direction] at = (!) • The outer walls of the grid, as well as any inner walls, may be created by suitable instantiation of these lists of directions. [ see text for details ]
Robot Simulator • The graphics required for the robot simulator presents no new difficulties, except for an issue regarding “incrementally” updating the graphics image, rather than redrawing everything as we have previously done. drawGrid :: Window -> Grid -> IO () drawCoins :: Window -> RobotState -> IO ()[ see text for details ]
Putting It All Together • We need a function that takes a robot program, an initial state, and an initial grid, and then “executes” the program:runRobot :: Robot () -> RobotState -> Grid -> IO ()runRobot (Robot sf) s g = runGraphics $ do w <- openWindowEx "Robot World" (Just (0,0)) (Just (xWin,yWin)) drawGraphic (Just 10) drawGrid w g -- draws the grid drawCoins w s -- draws the coins spaceWait w -- waits for spacebar press sf s g w -- executes program spaceClose w -- waits for spacebar press