cse536 functional programming 1 6/10/2015 lecture 10, oct. 29, 2004 special rescheduled friday...

34
Cse536 Functional Programming 1 06/20/22 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics Pictures Low level graphics bit-maps: G.Region From Region to G.Region » Shape to G.Region Drawing G.Region Reactive Pictures Reading Assignment Read Chapter 10: Drawing Regions Reminder: Homework Assignment #5 (was assigned last Monday but is due next Wednesday, the day of the midterm)

Post on 19-Dec-2015

217 views

Category:

Documents


1 download

TRANSCRIPT

Page 1: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

104/18/23

Lecture 10, Oct. 29, 2004•Special Rescheduled Friday Lecture•Today’s Topics

– Pictures

– Low level graphics bit-maps: G.Region

– From Region to G.Region

» Shape to G.Region

–Drawing G.Region

–Reactive Pictures

•Reading Assignment– Read Chapter 10: Drawing Regions

•Reminder: Homework Assignment #5 (was assigned last Monday but is due next Wednesday, the day of the midterm)

Page 2: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

204/18/23

Remember, Guest Lecture and Exam

Sun Mon Tue Wed Thu Fri Sat

31 Nov 1 2 3Midtermexam

4 5 6

Guest Lect.

Tom Harke

The Haskell Class System

Page 3: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

304/18/23

Pictures• Drawing Pictures

– Pictures are composed of Regions

» Regions are composed of shapes

– Pictures add Color

data Picture = Region Color Region

| Picture `Over` Picture

| EmptyPic

deriving Show

Must be careful to use SOEGraphics, butSOEGraphics has its own Region datatype.

import SOEGraphics hiding (Region)

import qualified SOEGraphics as G (Region)

Page 4: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

404/18/23

Recall our Region datatypedata Region =

Shape Shape -- primitive shape

| Translate Vector Region -- translated region

| Scale Vector Region -- scaled region

| Complement Region -- inverse of region

| Region `Union` Region -- union of regions | Region `Intersect` Region -- intersection of regions

| Empty

deriving Show

How will we draw things like the intersection of two regions, or the complement of two regions. These are hard things to do, and require hardware support to do efficiently. The G.Region type interfaces to this hardware support.

Page 5: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

504/18/23

G.Region• The G.Region datatype interfaces to the

hardware. It is essentially a two dimensional array or “bit-map”, storing a binary value for each pixel in the window.

Page 6: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

604/18/23

Hardware support• There is efficient hardware support for

combining two bit-maps using binary operators.

• Operations are fast, but data (space) intensive, and this space needs to be explicitly allocated and de-allocated.

+ =

Page 7: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

704/18/23

Interface

createRectangle :: Point -> Point -> IO G.Region

createEllipse :: Point -> Point -> IO G.Region

createPolygon :: [Point] -> IO G.Region

andRegion :: G.Region -> G.Region -> IO G.Region

orRegion :: G.Region -> G.Region -> IO G.Region

xorRegion :: G.Region -> G.Region -> IO G.Region

diffRegion :: G.Region -> G.Region -> IO G.Region

deleteRegion :: G.Region -> IO ()

drawRegion :: G.Region -> Graphic

These functions are defined in the SOEGraphics library

module.

Page 8: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

804/18/23

Drawing G.Region

• To draw things quickly, turn them into a G.Region, then turn the G.Region into a graphic object and then use all the machinery we have built up so far.

drawRegionInWindow::Window -> Color -> Region -> IO ()

drawRegionInWindow w c r =

drawInWindow w

(withColor c (drawRegion (regionToGRegion r)))

• All we need to define then is: regionToGRegion– we’ll come back to regionToGRegion in a minute

Page 9: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

904/18/23

Drawing Pictures•Pictures combine multiple regions

into one big picture. They provide a mechanism for placing one sub-picture on top of another.

drawPic :: Window -> Picture -> IO ()

drawPic w (Region c r) = drawRegionInWindow w c r

drawPic w (p1 `Over` p2) = do { drawPic w p2

; drawPic w p1

}

drawPic w EmptyPic = return ()

Page 10: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

1004/18/23

Overview• We have a rich calculus of Shapes, which we can

draw, take the perimeter of, and tell if a point lies within.

• We extend this with a richer type Region, which allows more complicated ways of combination (intersection, complement, etc.). – We gave Region a mathematical semantics as a set of points in the 2-

dimensional plane.

– We defined some interesting operators like containsR which is the characteristic function for a region.

– The rich combination ability make Region hard to draw efficiently, so we use a lower level datatype supported by the hardware: G.Region which is essentially a bit-map.

• We enrich this even further with the Picture type.• G.Region is low level, relying on features like

overwriting, and explicit allocation and deallocation of memory.– We think of Region, as a highlevel interface to G.Region which hides the

low level details.

Page 11: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

1104/18/23

Turning a Region into a G.RegionExperiment with a smaller problem to illustrate a

lurking efficiency problem.

data NewRegion = Rect Side Side -- Abstracts G.Region

regToNReg1 :: Region -> NewRegion

regToNReg1 (Shape (Rectangle sx sy))

= Rect sx sy

regToNReg1 (Scale (x,y) r)

= regToNReg1 (scaleReg (x,y) r)

where scaleReg (x,y) (Shape (Rectangle sx sy))

= Shape (Rectangle (x*sx) (y*sy))

scaleReg (x,y) (Scale s r)

= Scale s (scaleReg (x,y) r)

Note, scaleReg distributes over

Scale

Page 12: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

1204/18/23

Problem•Consider

(Scale (x1,y1)

(Scale (x2,y2)

(Scale (x3,y3)

... (Shape (Rectangle sx sy))

… )))

• If the Scale level is N-deep, how many traversals does regToNReg1 do of the Region tree?

Page 13: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

1304/18/23

We’ve seen this before•Believe it or not we have encountered

this problem before. Recall the definition of reversereverse [] = []

reverse (x:xs) = (reverse xs) ++ [x]

where [] ++ zs = zs

(y:ys) ++ zs = y : (ys ++ zs)

•How did we solve this? Use an extra accumulating parameter.reverse xs = revhelp xs []

where revhelp [] zs = zs

revhelp (x:xs) zs = revhelp xs (x:zs)

Page 14: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

1404/18/23

Accumulate a complex Scale

regToNReg2 :: Region -> NewRegion

regToNReg2 r = rToNR (1,1) r

where rToNR :: (Float,Float) -> Region -> NewRegion

rToNR (x1,y1) (Shape (Rectangle sx sy))

= Rect (x1*sx) (y1*sy)

rToNR (x1,y1) (Scale (x2,y2) r)

= rToNR (x1*x2,y1*y2) r

• To solve our original problem Repeat this for all the constructors of Region (not just Shape and Scale) and use G.Region instead of NewRegion, We also need to handle translation as well as scaling

Page 15: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

1504/18/23

Final VersionregToGReg1 :: Vector -> Vector -> Region -> G.Region

regToGReg1 trans sca (Shape s) = shapeToGRegion trans sca s

regToGReg1 (x,y) sca (Translate (u,v) r)

= regToGReg1 (x+u, y+v) sca r

regToGReg1 trans (x,y) (Scale (u,v) r)

= regToGReg1 trans (x*u, y*v) r

regToGReg1 trans sca Empty = createRectangle (0,0) (0,0)

regToGReg1 trans sca (r1 `Union` r2)

= let gr1 = regToGReg1 trans sca r1

gr2 = regToGReg1 trans sca r2

in orRegion gr1 gr2

• Assuming of course we can write: shapeToGRegion :: Vector -> Vector -> Shape -> G.Region

and write rules for Intersect, Complement etc.

Page 16: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

1604/18/23

A matter of style

• While the function on the previous page shows how to solve the problem, there are several stylistic issues that could make it more readable and understandable.

• The style of defining a function by patterns, becomes cluttered when there are many parameters (other than the one which has the patterns).

• The pattern of explicitly allocating and deallocating (bit-map) G.Region’s will be repeated in cases for intersection and for complement, so we should abstract it, and give it a name.

Page 17: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

1704/18/23

Abstract the low level bit-map details

primGReg trans sca r1 r2 op

= let gr1 = regToGReg trans sca r1

gr2 = regToGReg trans sca r2

in op gr1 gr2

Page 18: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

1804/18/23

Redo with a case expression

regToGReg :: Vector -> Vector -> Region -> G.RegionregToGReg (trans @ (x,y)) (sca @ (a,b)) shape = case shape of (Shape s) -> shapeToGRegion trans sca s (Translate (u,v) r) -> regToGReg (x+u, y+v) sca r (Scale (u,v) r) -> regToGReg trans (a*u, b*v) r (Empty) -> createRectangle (0,0) (0,0) (r1 `Union` r2) -> primGReg trans sca r1 r2 orRegion (r1 `Intersect` r2) -> primGReg trans sca r1 r2 andRegion (Complement r) -> primGReg trans sca winRect r diffRegion where winRect :: Region winRect = Shape (Rectangle (pixelToInch xWin) (pixelToInch yWin))

regionToGRegion :: Region -> G.RegionregionToGRegion r = regToGReg (0,0) (1,1) r

Pattern renaming

Page 19: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

1904/18/23

Shape to G.Region: RectanglexWin2 = xWin `div` 2

yWin2 = yWin `div` 2

shapeToGRegion1

:: Vector -> Vector -> Shape -> IO G.Region

shapeToGRegion1 (lx,ly) (sx,sy) (Rectangle s1 s2)

= createRectangle (trans(-s1/2,-s2/2)) (trans (s1/2,s2/2))

where trans (x,y) = ( xWin2 + inchToPixel ((x+lx)*sx),

yWin2 - inchToPixel ((y+ly)*sy) )

( xWin2, yWin2)

( xWin, yWin )

s1

s2s1/2 S2/2

Translation details

scaling details

Page 20: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

2004/18/23

EllipseshapeToGRegion1 (lx,ly) (sx,sy) (Ellipse r1 r2)

= createEllipse (trans (-r1,-r2)) (trans ( r1, r2))

where trans (x,y) =

( xWin2 + inchToPixel ((x+lx)*sx),

yWin2 - inchToPixel ((y+ly)*sy) )

r1

r2

Page 21: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

2104/18/23

Polygon and RtTriangle

shapeToGRegion1 (lx,ly) (sx,sy) (Polygon pts)

= createPolygon (map trans pts)

where trans (x,y) =

( xWin2 + inchToPixel ((x+lx)*sx),

yWin2 - inchToPixel ((y+ly)*sy) )

shapeToGRegion1 (lx,ly) (sx,sy) (RtTriangle s1 s2) = createPolygon (map trans [(0,0),(s1,0),(0,s2)]) where trans (x,y) =

( xWin2 + inchToPixel ((x+lx)*sx), yWin2 - inchToPixel ((y+ly)*sy) )

Page 22: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

2204/18/23

A matter of style, again• shapeToGRegion1 has the same problems as

regToGReg1 – The extra translation and scaling parameters obscure the pattern

matching– There is a repeated pattern, we should give it a name.

shapeToGRegion (lx,ly) (sx,sy) s = case s of Rectangle s1 s2 -> createRectangle (trans (-s1/2,-s2/2)) (trans (s1/2,s2/2)) Ellipse r1 r2 -> createEllipse (trans (-r1,-r2)) (trans ( r1, r2)) Polygon pts -> createPolygon (map trans pts) RtTriangle s1 s2 -> createPolygon (map trans [(0,0),(s1,0),

(0,s2)]) where trans (x,y) = ( xWin2 + inchToPixel ((x+lx)*sx), yWin2 - inchToPixel ((y+ly)*sy) )

Page 23: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

2304/18/23

Drawing Pictures, Sample Regions

draw :: Picture -> IO ()

draw p

= runGraphics (

do w <- openWindow "Region Test" (xWin,yWin)

drawPic w p

spaceClose w

)

r1 = Shape (Rectangle 3 2)

r2 = Shape (Ellipse 1 1.5)

r3 = Shape (RtTriangle 3 2)

r4 = Shape (Polygon [(-2.5,2.5), (-3.0,0),

(-1.7,-1.0),

(-1.1,0.2), (-1.5,2.0)] )

Page 24: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

2404/18/23

Sample Pictures

reg1 = r3 `Union` --RtTriangle

r1 `Intersect` -- Rectangle

Complement r2 `Union` -- Ellispe

r4 -- Polygon

pic1 = Region Cyan reg1

Main1 = draw pic1

Recall the precedence

of Union and Intersect

Page 25: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

2504/18/23

More Picturesreg2 = let circle = Shape (Ellipse 0.5 0.5)

square = Shape (Rectangle 1 1)

in (Scale (2,2) circle)

`Union` (Translate (2,1) square)

`Union` (Translate (-2,0) square)

pic2 = Region Yellow reg2

main2 = draw pic2

Page 26: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

2604/18/23

Another Picture

pic3 = pic2 `Over` pic1

main3 = draw pic3

Page 27: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

2704/18/23

Separate computation from actiononeCircle = Shape (Ellipse 1 1)manyCircles = [ Translate (x,0) oneCircle | x <- [0,2..] ]fiveCircles = foldr Union Empty (take 5 manyCircles)pic4 = Region Magenta (Scale (0.25,0.25) fiveCircles)main4 = draw pic4

Page 28: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

2804/18/23

Ordering Pictures

pictToList :: Picture -> [(Color,Region)]

pictToList EmptyPic = []pictToList (Region c r) = [(c,r)]pictToList (p1 `Over` p2) = pictToList p1 ++ pictToList p2

pic6 = pic4 `Over` pic2 `Over` pic1 `Over` pic5pictToList pic6 - - - > [(Magenta,?), (yellow,?),(Cyan,?),(Cyan,?)]

Recovers the Regions from top to bottompossible because Picture is a datatype that can be analysed

Page 29: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

2904/18/23

An AnalogypictToList EmptyPic = []

pictToList (Region c r) = [(c,r)]

pictToList (p1 `Over` p2)

= pictToList p1 ++ pictToList p2

drawPic w (Region c r) = drawRegionInWindow w c r

drawPic w (p1 `Over` p2) = do { drawPic w p2

; drawPic w p1}

drawPic w EmptyPic = return ()

• Something to prove:sequence .

(map (uncurry (drawRegionInWindow w))) . Reverse . pictToList

= drawPic w

Page 30: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

3004/18/23

Pictures that React• Find the Topmost Region in a picture that

“covers” the position of the mouse when a left button click appears.

• Search the picturelist for the the first Region that contains the mouse position.

• Re-arrange the list, bring that one to the top

adjust :: [(Color,Region)] -> Vertex ->

(Maybe (Color,Region), [(Color,Region)])

adjust [] p = (Nothing, [])

adjust ((c,r):regs) p =

if r `containsR` p

then (Just (c,r), regs)

else let (hit, rs) = adjust regs p

in (hit, (c,r) : rs)

Page 31: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

3104/18/23

Doing it Non-recursively

adjust2 regs p

= case (break (\(_,r) -> r `containsR` p) regs) of

(top,hit:rest) -> (Just hit, top++rest)

(_,[]) -> (Nothing, [])

break:: (a -> Bool) -> [a] -> ([a],[a])

is from the Prelude.

Break even [1,3,5,4,7,6,12]

([1,3,5],[4,7,6,12])

Page 32: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

3204/18/23

Putting it all togetherloop :: Window -> [(Color,Region)] -> IO ()

loop w regs =

do clearWindow w

sequence [ drawRegionInWindow w c r |

(c,r) <- reverse regs ]

(x,y) <- getLBP w

case (adjust regs (pixelToInch (x - xWin2),

pixelToInch (yWin2 - y) )) of

(Nothing, _ ) -> closeWindow w

(Just hit, newRegs) -> loop w (hit : newRegs)

draw2 :: Picture -> IO ()

draw2 pic

= runGraphics (

do w <- openWindow "Picture demo" (xWin,yWin)

loop w (pictToList pic))

Page 33: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

3304/18/23

Try it out

p1,p2,p3,p4 :: Picture

p1 = Region Magenta r1

p2 = Region Cyan r2

p3 = Region Green r3

p4 = Region Yellow r4

pic :: Picture

pic = foldl Over EmptyPic [p1,p2,p3,p4]

main = draw2 pic

Page 34: Cse536 Functional Programming 1 6/10/2015 Lecture 10, Oct. 29, 2004 Special Rescheduled Friday Lecture Today’s Topics – Pictures – Low level graphics bit-maps:

Cse536 Functional Programming

3404/18/23

A matter of style, 3loop2 w regs

= do clearWindow w

sequence [ drawRegionInWindow w c r |

(c,r) <- reverse regs ]

(x,y) <- getLBP w

let aux (_,r) = r `containsR`

( pixelToInch (x-xWin2),

pixelToInch (yWin2-y) )

case (break aux regs) of

(_,[]) -> closeWindow w

(top,hit:bot) -> loop w (hit : (top++bot))

draw3 :: Picture -> IO ()

draw3 pic

= runGraphics (

do w <- openWindow "Picture demo" (xWin,yWin)

loop2 w (pictToList pic) )