Chapter 19 An Imperative Robot Language. Motivation  In the previous chapter, monads were introduced.  In particular, state monads were described as.

Slides:



Advertisements
Similar presentations
Summer Computing Workshop. Introduction to Variables Variables are used in every aspect of programming. They are used to store data the programmer needs.
Advertisements

Programming with App Inventor Computing Institute for K-12 Teachers Summer 2012 Workshop.
Haskell Chapter 7. Topics  Defining data types  Exporting types  Type parameters  Derived instances  Type synonyms  Either  Type classes  Not.
RAPTOR Syntax and Semantics By Lt Col Schorsch
Kathleen Fisher cs242 Reading: “A history of Haskell: Being lazy with class”,A history of Haskell: Being lazy with class Section 6.4 and Section 7 “Monads.
Programming with Alice Computing Institute for K-12 Teachers Summer 2011 Workshop.
They’re not just binary anymore!
Grab Bag of Interesting Stuff. Topics Higher kinded types Files and handles IOError Arrays.
0 PROGRAMMING IN HASKELL Chapter 5 - List Comprehensions.
Chapter 3 Simple Graphics. Side Effects and Haskell  All the programs we have seen so far have no “side-effects.” That is, programs are executed only.
Complexity Analysis (Part I)
Precedence Parentheses Arithemetic ^ * / + - (exception logical not ~ ) Relational > =
Chapter 13 A Module of Simple Animations. Motivation  In the abstract, an animation is a continuous, time-varying image.  But in practice, it is a sequence.
CS 117 Spring 2002 Repetition Hanly Chapter 4 Friedman-Koffman Chapter 5.
Chapter 5, CLR Textbook Algorithms on Grids of Processors.
Advanced Programming Handout 10 A Module of Simple Animations (SOE Chapter 13)
Precedence Parentheses Arithemetic ^ * / + - (exception logical not ~ ) Relational > =
Chapter 5 Polymorphic and Higher-Order Functions.
Guide To UNIX Using Linux Third Edition
VHDL. What is VHDL? VHDL: VHSIC Hardware Description Language  VHSIC: Very High Speed Integrated Circuit 7/2/ R.H.Khade.
Chapter Day 9. © 2007 Pearson Addison-Wesley. All rights reserved4-2 Agenda Day 8 Questions from last Class?? Problem set 2 posted  10 programs from.
CS510AP Quick Check Monads. QuickCheck Quick check is a Haskell library for doing random testing. You can read more about quickcheck at –
Week 7 - Programming II Today – more features: – Loop control – Extending if/else – Nesting of loops Debugging tools Textbook chapter 7, pages
Copyright 2010 by Pearson Education 1 Assignment 11: Critters.
Turtle Graphics  Turtle graphics provide a simple way to draw pictures in a window.  The name suggests the way in which we can think about the drawing.
Games and Simulations O-O Programming in Java The Walker School
Instructor: Chris Trenkov Hands-on Course Python for Absolute Beginners (Spring 2015) Class #005 (April somthin, 2015)
1 karel_part5_loops Iteration (Loops) Loops repeat a set of instructions Two types of loops: –Definite loops ( for ) perform instructions explicit (known)
Ch. 2 1 Karel – Primitive Instructions Basic tools with which all problems are solved (analogies: LeftSpinngingRobot, RightSpinningRobot, GuardRobot, etc)
Karel J Robot An introduction to BlueJ and Object- Oriented Programming.
OOD Case Study (For parallel treatment, see Chapter 2 of the text)
Computer Program A sequence of step-by-step instructions for the computer to follow Why bother? Demo: Human vs. Computer following instructions.
Karel the Robot A Gentle Introduction to the Art of Programming.
Chapter 4: Decision Making with Control Structures and Statements JavaScript - Introductory.
Object-Oriented Programming. Object-oriented programming  First goal: Define and describe the objects of the world  Noun-oriented  Focus on the domain.
Microsoft® Small Basic
Turtle Graphics  Turtle graphics provide a simple way to draw pictures in a window.  The name suggests the way in which we can think about the drawing.
1 Turtle Graphics and Math Functions And how you can use them to draw cool pictures!
Java is an object oriented programming language In this model of programming all entities are objects that have methods and fields Methods perform tasks.
Summer Computing Workshop. Introduction  Boolean Expressions – In programming, a Boolean expression is an expression that is either true or false. In.
Smalltalk (and Squeak) Aida Dungan and Rick Shreve.
1 karel_part2_Inheritance Extending Robots Tired of writing turnRight every time you start a new karel project. How do we avoid re-writing code all the.
Concurrent Programming and Threads Threads Blocking a User Interface.
© M. Winter COSC 4P41 – Functional Programming Programming with actions Why is I/O an issue? I/O is a kind of side-effect. Example: Suppose there.
© M. Winter COSC 4P41 – Functional Programming Modules in Haskell Using modules to structure a large program has a number of advantages: Parts of.
Computing and Statistical Data Analysis Lecture 2 Glen Cowan RHUL Physics Computing and Statistical Data Analysis Variables, types: int, float, double,
Sections © Copyright by Pearson Education, Inc. All Rights Reserved.
 In the java programming language, a keyword is one of 50 reserved words which have a predefined meaning in the language; because of this,
Programming in Karel Eric Roberts CS 106A January 6, 2016.
0 PROGRAMMING IN HASKELL Chapter 4 - Defining Functions.
Chapter 7: Repetition Structure (Loop) Department of Computer Science Foundation Year Program Umm Alqura University, Makkah Computer Programming Skills.
M1G Introduction to Programming 2 2. Creating Classes: Game and Player.
Chapter 9 Nested Loops and Two-Dimensional Arrays Lecture Slides to Accompany An Introduction to Computer Science Using Java (2nd Edition) by S.N. Kamin,
BIT 115: Introduction To Programming Professor: Dr. Baba Kofi Weusijana Pronounced Bah-bah Co-fee Way-ou-see-jah-nah Call him “Baba” or “Dr. Weusijana”
Set Comprehensions In mathematics, the comprehension notation can be used to construct new sets from old sets. {x2 | x  {1...5}} The set {1,4,9,16,25}
Set Comprehensions In mathematics, the comprehension notation can be used to construct new sets from old sets. {x2 | x  {1...5}} The set {1,4,9,16,25}
Haskell Chapter 7.
Vocabulary Algorithm - A precise sequence of instructions for processes that can be executed by a computer Low level programming language: A programming.
Haskell Chapter 2.
Algorithm Analysis CSE 2011 Winter September 2018.
A Tiny Look at the Graphics Window
Displaying sensor values while a robot is running
Microsoft® Small Basic
PROGRAMMING IN HASKELL
CSCE 314: Programming Languages Dr. Dylan Shell
Haskell Types, Classes, and Functions, Currying, and Polymorphism
PROGRAMMING IN HASKELL
CSE 3302 Programming Languages
A Tiny Look at the Graphics Window
U3L4 Using Simple Commands
Presentation transcript:

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 Bool isnt:: Robot Bool -> Robot Bool motion pen treasure control

Example: Spiral Motion spiral :: Robot () spiral = penDown >> loop 1 where loop n = lettwice = 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 Show type Position = (Int, Int)-- a grid data 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 facing blocked :: 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 -> Position movePos (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 Bool onCoin = queryState (\s -> position s `elem` treasure s) coins :: Robot Int coins = queryState pocket pickCoin :: 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 -> 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 a cond p c a= do pred Robot () -> Robot () while p b= cond1 p (b >> while p b) (||*):: Robot Bool -> Robot Bool -> Robot Bool b1 ||* b2= do p Robot Bool isnt= liftM not (>*), ( Robot Int -> Robot Bool (>*)= liftM2 (>) (<*)= liftM2 (<) [ similarly for (&&*) ]

Haskell Arrays  Arrays in Haskell have type: Ix a => Array a b where “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