Added programming language fundamentals code. More to come.

This commit is contained in:
2018-01-06 23:10:08 -08:00
parent 51b0102711
commit 7b18f6a807
13 changed files with 1248 additions and 0 deletions

View File

@@ -0,0 +1,63 @@
-- | This module defines the syntax of MiniMiniLogo. It also provides
-- functions to generate programs that draw some basic shapes.
--
-- NOTE: You should not change the definitions in this file!
--
module MiniMiniLogo where
--
-- * Syntax
--
-- | A program is a sequence of commands.
type Prog = [Cmd]
-- | The mode of the pen.
data Mode = Down | Up
deriving (Eq,Show)
-- | Abstract syntax of commands.
data Cmd = Pen Mode
| Move Int Int
deriving (Eq,Show)
-- | Generate a MiniMiniLogo program that draws a 2x2 box starting from the
-- specified point. Conceptually, this program looks like the following, but
-- the additions are carried out in Haskell rather than in MiniMiniLogo.
--
-- pen up; move (x,y);
-- pen down; move (x+2,y); move (x+2,y+2);
-- move (x,y+2); move (x,y);
--
-- >>> box 7 3
-- [Pen Up,Move 7 3,Pen Down,Move 9 3,Move 9 5,Move 7 5,Move 7 3]
--
box :: Int -> Int -> Prog
box x y = [Pen Up, Move x y, Pen Down,
Move (x+2) y, Move (x+2) (y+2), Move x (y+2), Move x y]
-- | Generate an 'X' from (x,y) to (x+w,y+h).
--
-- >>> nix 10 10 5 7
-- [Pen Up,Move 10 10,Pen Down,Move 15 17,Pen Up,Move 10 17,Pen Down,Move 15 10]
--
nix :: Int -> Int -> Int -> Int -> Prog
nix x y w h = [Pen Up, Move x y, Pen Down, Move (x+w) (y+h),
Pen Up, Move x (y+h), Pen Down, Move (x+w) y]
-- | Generate a MiniMiniLogo program that draws n steps starting from
-- point (x,y).
--
-- >>> steps 3 2 4
-- [Pen Up,Move 2 4,Pen Down,Move 2 5,Move 3 5,Move 3 6,Move 4 6,Move 4 7,Move 5 7]
--
steps :: Int -> Int -> Int -> Prog
steps n x y = [Pen Up, Move x y, Pen Down] ++ step n
where
step 0 = []
step n = step (n-1) ++ [Move (x+n-1) (y+n), Move (x+n) (y+n)]
-- | Draw an example picture. The expected output is given on the HW4
-- description page.
demo :: Prog
demo = box 7 3 ++ nix 6 6 4 3 ++ steps 3 2 4

View File

@@ -0,0 +1,13 @@
<!DOCTYPE html>
<html>
<head><title>MiniLogo Semantics Viewer</title></head>
<body>
<svg width='100%' viewBox='0 0 820 420'>
<rect x='7' y='7' width='806' height='405' style='fill:none;stroke:black;stroke-width:2'/>
<polyline points='80,380 100,380 100,360 80,360 80,380' style='fill:white;stroke:red;stroke-width:2'/>
<polyline points='70,350 110,320' style='fill:white;stroke:red;stroke-width:2'/>
<polyline points='70,320 110,350' style='fill:white;stroke:red;stroke-width:2'/>
<polyline points='30,370 30,360 40,360 40,350 50,350 50,340 60,340' style='fill:white;stroke:red;stroke-width:2'/>
</svg>
</body>
</html>

View File

@@ -0,0 +1,120 @@
module MiniMiniLogoSem where
import MiniMiniLogo
import Render
--NOTES -----------------------------------------------
-- -- | A program is a sequence of commands.
-- type Prog = [Cmd]
-- -- | The mode of the pen.
-- data Mode = Down | Up
-- deriving (Eq,Show)
-- -- | Abstract syntax of commands.
-- data Cmd = Pen Mode
-- | Move Int Int
-- deriving (Eq,Show)
-- -- | A point is a cartesian pair (x,y).
-- type Point = (Int,Int)
-- -- | A line is defined by its endpoints.
-- type Line = (Point,Point)
-------------------------------------------------------
--
-- * Semantics of MiniMiniLogo
--
-- NOTE:
-- * MiniMiniLogo.hs defines the abstract syntax of MiniMiniLogo and some
-- functions for generating MiniMiniLogo programs. It contains the type
-- definitions for Mode, Cmd, and Prog.
-- * Render.hs contains code for rendering the output of a MiniMiniLogo
-- program in HTML5. It contains the types definitions for Point and Line.
-- | A type to represent the current state of the pen.
type State = (Mode,Point)
-- | The initial state of the pen.
start :: State
start = (Up,(0,0))
-- | A function that renders the image to HTML. Only works after you have
-- implemented `prog`. Applying `draw` to a MiniMiniLogo program will
-- produce an HTML file named MiniMiniLogo.html, which you can load in
-- your browswer to view the rendered image.
draw :: Prog -> IO ()
draw p = let (_,ls) = prog p start in toHTML ls
-- Semantic domains:
-- * Cmd: State -> (State, Maybe Line)
-- * Prog: State -> (State, [Line])
-- | Semantic function for Cmd.
--
-- >>> cmd (Pen Down) (Up,(2,3))
-- ((Down,(2,3)),Nothing)
--
-- >>> cmd (Pen Up) (Down,(2,3))
-- ((Up,(2,3)),Nothing)
--
-- >>> cmd (Move 4 5) (Up,(2,3))
-- ((Up,(4,5)),Nothing)
--
-- >>> cmd (Move 4 5) (Down,(2,3))
-- ((Down,(4,5)),Just ((2,3),(4,5)))
--
cmd :: Cmd -> State -> (State, Maybe Line)
cmd (Pen x) (_,pt) = ( (x,pt) , Nothing)
cmd (Move m1 m2) (Down,pt) = ( (Down, (m1,m2)) , Just((pt),(m1,m2)) )
cmd (Move m1 m2) (Up,pt) = ( (Up, (m1,m2)) , Nothing)
-- | Semantic function for Prog.
--
-- >>> prog (nix 10 10 5 7) start
-- ((Down,(15,10)),[((10,10),(15,17)),((10,17),(15,10))])
--
-- >>> prog (steps 2 0 0) start
-- ((Down,(2,2)),[((0,0),(0,1)),((0,1),(1,1)),((1,1),(1,2)),((1,2),(2,2))])
prog :: Prog -> State -> (State, [Line])
prog prgs st = (progHelper prgs (st,[]) )
progHelper :: Prog -> (State, [Line]) -> (State, [Line])
progHelper [] x = x
progHelper (prg:prgs) (st,ls) =
let (nexst,nexln) = cmd prg st in
case nexln of
Just nexln -> progHelper prgs (nexst,ls ++ [nexln])
Nothing -> progHelper prgs (nexst,ls)
-- | Makes life ez
-- How to run 101
-- ezRander (prog (nix 10 10 5 7) start)
ezRender :: (State,[Line]) -> IO ()
ezRender (_,xs) = toHTML xs
--
-- * Extra credit
--
-- | This should be a MiniMiniLogo program that draws an amazing picture.
-- Add as many helper functions as you want.
-- ezRender(prog amazing start)
amazing :: Prog
amazing = [Pen Up, Move 5 5,Pen Down, Move 20 5, Move 20 10, Move 5 10, Move 5 5, Pen Up] ++ (steps 5 20 10)
++ [Pen Up, Move 5 10, Pen Down, Move 3 13, Pen Up] ++ (bigbox 0 13)
++ [Pen Up, Move 0 17, Pen Down, Move 1 19,Move 2 17, Move 3 19, Move 4 17, Pen Up]
++ [Pen Up, Move 7 5, Pen Down, Move 7 0, Pen Up]
++ [Pen Up, Move 17 5, Pen Down, Move 17 0, Pen Up]
bigbox :: Int -> Int -> Prog
bigbox x y = [Pen Up, Move x y, Pen Down,
Move (x+4) y, Move (x+4) (y+4), Move x (y+4), Move x y]

View File

@@ -0,0 +1,80 @@
module MiniMiniLogoSem where
import MiniMiniLogo
import Render
--
-- * Semantics of MiniMiniLogo
--
-- NOTE:
-- * MiniMiniLogo.hs defines the abstract syntax of MiniMiniLogo and some
-- functions for generating MiniMiniLogo programs. It contains the type
-- definitions for Mode, Cmd, and Prog.
-- * Render.hs contains code for rendering the output of a MiniMiniLogo
-- program in HTML5. It contains the types definitions for Point and Line.
-- | A type to represent the current state of the pen.
type State = (Mode,Point)
-- | The initial state of the pen.
start :: State
start = (Up,(0,0))
-- | A function that renders the image to HTML. Only works after you have
-- implemented `prog`. Applying `draw` to a MiniMiniLogo program will
-- produce an HTML file named MiniMiniLogo.html, which you can load in
-- your browswer to view the rendered image.
draw :: Prog -> IO ()
draw p = let (_,ls) = prog p start in toHTML ls
-- Semantic domains:
-- * Cmd: State -> (State, Maybe Line)
-- * Prog: State -> (State, [Line])
-- | Semantic function for Cmd.
--
-- >>> cmd (Pen Down) (Up,(2,3))
-- ((Down,(2,3)),Nothing)
--
-- >>> cmd (Pen Up) (Down,(2,3))
-- ((Up,(2,3)),Nothing)
--
-- >>> cmd (Move 4 5) (Up,(2,3))
-- ((Up,(4,5)),Nothing)
--
-- >>> cmd (Move 4 5) (Down,(2,3))
-- ((Down,(4,5)),Just ((2,3),(4,5)))
--
-- Done
cmd :: Cmd -> State -> (State, Maybe Line)
cmd (Pen s) (m, p) = ((s, p), Nothing)
cmd (Move x1 y1) (s, (x2, y2)) = case s of
Down -> ((s,(x1, y1)),Just ((x2,y2),(x1,y1)))
Up -> ((s,(x1, y1)),Nothing)
-- | Semantic function for Prog.
--
-- >>> prog (nix 10 10 5 7) start
-- ((Down,(15,10)),[((10,10),(15,17)),((10,17),(15,10))])
--
-- >>> prog (steps 2 0 0) start
-- ((Down,(2,2)),[((0,0),(0,1)),((0,1),(1,1)),((1,1),(1,2)),((1,2),(2,2))])
--
--
prog :: Prog -> State -> (State, [Line])
prog p (s, (x,y)) = ((s,(x,y)), prog p)
--
-- * Extra credit
--
-- | This should be a MiniMiniLogo program that draws an amazing picture.
-- Add as many helper functions as you want.
amazing :: Prog
amazing = undefined

View File

@@ -0,0 +1,86 @@
module MiniMiniLogoSem where
import MiniMiniLogo
import Render
--
-- * Semantics of MiniMiniLogo
--
-- NOTE:
-- * MiniMiniLogo.hs defines the abstract syntax of MiniMiniLogo and some
-- functions for generating MiniMiniLogo programs. It contains the type
-- definitions for Mode, Cmd, and Prog.
-- * Render.hs contains code for rendering the output of a MiniMiniLogo
-- program in HTML5. It contains the types definitions for Point and Line.
-- | A type to represent the current state of the pen.
type State = (Mode,Point)
-- | The initial state of the pen.
start :: State
start = (Up,(0,0))
-- | A function that renders the image to HTML. Only works after you have
-- implemented `prog`. Applying `draw` to a MiniMiniLogo program will
-- produce an HTML file named MiniMiniLogo.html, which you can load in
-- your browswer to view the rendered image.
draw :: Prog -> IO ()
draw p = let (_,ls) = prog p start in toHTML ls
-- Semantic domains:
-- * Cmd: State -> (State, Maybe Line)
-- * Prog: State -> (State, [Line])
-- | Semantic function for Cmd.
--
-- >>> cmd (Pen Down) (Up,(2,3))
-- ((Down,(2,3)),Nothing)
--
-- >>> cmd (Pen Up) (Down,(2,3))
-- ((Up,(2,3)),Nothing)
--
-- >>> cmd (Move 4 5) (Up,(2,3))
-- ((Up,(4,5)),Nothing)
--
-- >>> cmd (Move 4 5) (Down,(2,3))
-- ((Down,(4,5)),Just ((2,3),(4,5)))
--
cmd :: Cmd -> State -> (State, Maybe Line)
cmd (Pen pen_state) (_, new_point) = ((pen_state, new_point), Nothing)
cmd (Move mx my) (Up, (start_point)) = ((Up, (mx, my)), Nothing)
cmd (Move mx my) (Down, (start_x, start_y)) = ((Down, (mx, my)), Just ((start_x, start_y),(mx, my)))
-- | Semantic function for Prog.
--
-- >>> prog (nix 10 10 5 7) start
-- ((Down,(15,10)),[((10,10),(15,17)),((10,17),(15,10))])
--
-- >>> prog (steps 2 0 0) start
-- ((Down,(2,2)),[((0,0),(0,1)),((0,1),(1,1)),((1,1),(1,2)),((1,2),(2,2))])
prog :: Prog -> State -> (State, [Line])
prog [] prog_state = (prog_state, [])
prog prog_list start_state = progLineListHelper prog_list (start_state, [])
-- Helper function to handle keeping track of the line list as we move through the program elements
progLineListHelper :: Prog -> (State, [Line]) -> (State, [Line])
progLineListHelper [] state_and_line_list = state_and_line_list
progLineListHelper (progs_head:progs_tail) (initial_state, initial_line_list) =
let (new_state, new_line_list) = cmd progs_head initial_state in
case new_line_list of
Just new_line_list -> progLineListHelper progs_tail (new_state, initial_line_list ++ [new_line_list])
Nothing -> progLineListHelper progs_tail (new_state, initial_line_list)
--
-- * Extra credit
--
-- | This should be a MiniMiniLogo program that draws an amazing picture.
-- Add as many helper functions as you want.
amazing :: Prog
amazing = undefined

View File

@@ -0,0 +1,71 @@
-- | A module for rendering lines as an HTML5 file containing an SVG image.
-- This can be used to visualize the denotational semantics of a MiniLogo
-- program.
--
-- NOTE: You should not change the definitions in this file!
--
module Render (Point,Line,toHTML) where
import Data.List (intercalate)
-- | A point is a cartesian pair (x,y).
type Point = (Int,Int)
-- | A line is defined by its endpoints.
type Line = (Point,Point)
-- | Output a list of lines as an HTML5 file containing an SVG image.
toHTML :: [Line] -> IO ()
toHTML ls = writeFile "MiniMiniLogo.html" (header ++ content ls ++ footer)
--
-- Private definitions. All definitions below this point will not be visible
-- from within a module that imports this module.
--
scale, margin, width, height :: Int
scale = 10
margin = 10
width = 800
height = 400
style = "fill:white;stroke:red;stroke-width:2"
title = "<head><title>MiniLogo Semantics Viewer</title></head>"
view = "<svg width='100%' viewBox='0 0 "
++ show (width + 2*margin) ++ " "
++ show (height + 2*margin) ++ "'>"
border = "<rect x='" ++ show (margin-3) ++
"' y='" ++ show (margin-3) ++
"' width='" ++ show (width +6) ++
"' height='" ++ show (height+5) ++
"' style='fill:none;stroke:black;stroke-width:2'/>"
header = unlines ["<!DOCTYPE html>", "<html>", title, "<body>", view, border]
footer = unlines ["</svg>","</body>","</html>"]
content :: [Line] -> String
content = unlines . map poly . chunk
-- | A canvas-adjusted point as a string.
point :: Point -> String
point (x,y) = show xp ++ "," ++ show yp
where xp = x*scale + margin
yp = height - y*scale + margin
-- | Chunk a bunch of lines into sequences of connected points.
chunk :: [Line] -> [[Point]]
chunk [] = []
chunk [(p,q)] = [[p,q]]
chunk ((p,q):ls) | q == head ps = (p:ps) : pss
| otherwise = [p,q] : ps : pss
where (ps:pss) = chunk ls
-- | Draw a sequence of connected points.
poly :: [Point] -> String
poly ps = "<polyline points='"
++ intercalate " " (map point ps)
++ "' style='" ++ style ++ "'/>"