Skip to content

Instantly share code, notes, and snippets.

@jstroem
Last active January 21, 2016 17:44
Show Gist options
  • Save jstroem/4549439 to your computer and use it in GitHub Desktop.
Save jstroem/4549439 to your computer and use it in GitHub Desktop.
CSE230 HW1
---
title: Homework #1, Due Friday, January 20th
---
Preliminaries
-------------
Before starting this assignment:
1. Read chapters 1 -- 3 of The Haskell School of Expression.
2. Download and install the [Glasgow Haskell Compiler (GHC)](http://www.haskell.org/ghc/).
3. Download the SOE code bundle from
[the Haskell School of Expression page](/static/SOE.tar.gz).
4. Verify that it works by changing into the `SOE/src` directory and
running `ghci Draw.lhs`, then typing `main0` at the prompt:
~~~
cd SOE/src
ghci Draw.lhs
*Draw> main0
~~~
You should see a window with some shapes in it.
**NOTE:** If you have trouble installing SOE, [see this page](soe-instructions.html)
5. Download the required files for this assignment: [hw1.tar.gz](/static/hw1.tar.gz).
Unpack the files and make sure that you can successfully run the main program (in `Main.hs`).
We've provided a `Makefile`, which you can use if you like. You should see this output:
~~~
Main: Define me!
~~~
Haskell Formalities
-------------------
We declare that this is the Hw1 module and import some libraries:
> module Hw1 where
> import SOE
> import Play
> import XMLTypes
> import Text.Printf
Part 1: Defining and Manipulating Shapes
----------------------------------------
You will write all of your code in the `hw1.lhs` file, in the spaces
indicated. Do not alter the type annotations --- your code must
typecheck with these types to be accepted.
The following are the definitions of shapes from Chapter 2 of SOE:
> data Shape = Rectangle Side Side
> | Ellipse Radius Radius
> | RtTriangle Side Side
> | Polygon [Vertex]
> deriving Show
>
> type Radius = Float
> type Side = Float
> type Vertex = (Float, Float)
1. Below, define functions `rectangle` and `rtTriangle` as suggested
at the end of Section 2.1 (Exercise 2.1). Each should return a Shape
built with the Polygon constructor.
> rectangle :: Side -> Side -> Shape
> rectangle x y = Rectangle x y
> rtTriangle :: Side -> Side -> Shape
> rtTriangle x y = RtTriangle x y
2. Define a function
> sides :: Shape -> Int
> sides (Rectangle _ _) = 4
> sides (RtTriangle _ _) = 3
> sides (Polygon x) = if (length x) > 2 then (length x) else 0
> sides (Ellipse _ _) = 42
which returns the number of sides a given shape has.
For the purposes of this exercise, an ellipse has 42 sides,
and empty polygons, single points, and lines have zero sides.
3. Define a function
> bigger :: Shape -> Float -> Shape
> bigger (Rectangle x y) e = Rectangle (x * e) (y * e)
> bigger (RtTriangle x y) e = RtTriangle (x * e) (y * e)
> bigger (Ellipse x y) e = Ellipse (x * e) (y * e)
> bigger (Polygon x) e = (Polygon x) -- This case dont make sense to do anything..
that takes a shape `s` and expansion factor `e` and returns
a shape which is the same as (i.e., similar to in the geometric sense)
`s` but whose area is `e` times the area of `s`.
4. The Towers of Hanoi is a puzzle where you are given three pegs,
on one of which are stacked $n$ discs in increasing order of size.
To solve the puzzle, you must move all the discs from the starting peg
to another by moving only one disc at a time and never stacking
a larger disc on top of a smaller one.
To move $n$ discs from peg $a$ to peg $b$ using peg $c$ as temporary storage:
1. Move $n - 1$ discs from peg $a$ to peg $c$.
2. Move the remaining disc from peg $a$ to peg $b$.
3. Move $n - 1$ discs from peg $c$ to peg $b$.
Write a function
> hanoi :: Int -> String -> String -> String -> IO ()
> hanoi 1 a b c = putStrLn(printf "move disc from %s to %s" a b)
> hanoi n a b c = do
> hanoi (n-1) a c b
> hanoi 1 a b c
> hanoi (n-1) c b a
that, given the number of discs $n$ and peg names $a$, $b$, and $c$,
where a is the starting peg,
emits the series of moves required to solve the puzzle.
For example, running `hanoi 2 "a" "b" "c"`
should emit the text
~~~
move disc from a to c
move disc from a to b
move disc from c to b
~~~
Part 2: Drawing Fractals
------------------------
1. The Sierpinski Carpet is a recursive figure with a structure similar to
the Sierpinski Triangle discussed in Chapter 3:
![Sierpinski Carpet](/static/scarpet.png)
Write a function `sierpinskiCarpet` that displays this figure on the
screen:
> sierpinskiCarpet :: IO ()
> sierpinskiCarpet = runGraphics(
> do w <- openWindow "sierpinskiCarpet" (400,400)
> siepinskiRectangle w 0 0 400 2
> k <- getKeyChar w
> closeWindow w
> )
Helper method #1: Doing the recursive walk:
> siepinskiRectangle :: Window -> Int -> Int -> Int -> Int -> IO ()
> siepinskiRectangle w x y size times =
> if times == 0
> then fillRectangle w x y size
> else let size2 = size `div` 3
> in do siepinskiRectangle w x y size2 (times - 1)
> siepinskiRectangle w x (y+size2) size2 (times - 1)
> siepinskiRectangle w x ((y+size2)+size2) size2 (times - 1)
> siepinskiRectangle w (x+size2) y size2 (times - 1)
> siepinskiRectangle w (x+size2) ((y+size2)+size2) size2 (times - 1)
> siepinskiRectangle w ((x+size2)+size2) y size2 (times - 1)
> siepinskiRectangle w ((x+size2)+size2) (y+size2) size2 (times - 1)
> siepinskiRectangle w ((x+size2)+size2) ((y+size2)+size2) size2 (times - 1)
Helper method #2: Drawing the rectangle:
> fillRectangle :: Window -> Int -> Int -> Int -> IO ()
> fillRectangle w x y size =
> drawInWindow w (withColor Blue (polygon [(x, y), (x+size,y), (x+size,y+size), (x,y+size), (x, y)]))
Note that you either need to run your program in `SOE/src` or add this
path to GHC's search path via `-i/path/to/SOE/src/`.
Also, the organization of SOE has changed a bit, so that now you use
`import SOE` instead of `import SOEGraphics`.
2. Write a function `myFractal` which draws a fractal pattern of your
own design. Be creative! The only constraint is that it shows some
pattern of recursive self-similarity.
> myFractal :: IO ()
> myFractal = runGraphics(
> do w <- openWindow "myFractal" (1000,1000)
> myFractalHouse w 0 0 1000 5
> k <- getKeyChar w
> closeWindow w
> )
> myFractalHouse :: Window -> Int -> Int -> Int -> Int -> IO ()
> myFractalHouse w x y size times =
> if times == 0
> then
> do drawBackground w x y size
> drawGrass w x y size
> drawHouse w x y size
> drawDoor w x y size
> drawRuff w x y size
> drawWindow w x y size
> drawSun w x y size
> else
> do myFractalHouse w x y size (times - 1)
> myFractalHouse w x (y+5*(size `div` 6)-(size `div` 4)) (size `div` 4) (times - 1)
> myFractalHouse w (x+3*(size `div` 4)) (y+5*(size `div` 6)-(size `div` 4)) (size `div` 4) (times - 1)
> myFractalHouse w (x+3*(size `div` 10)) (y+3*(size `div` 10)) (4*(size `div` 10)) (times - 1)
> drawGrass :: Window -> Int -> Int -> Int -> IO ()
> drawGrass w x y size =
> drawInWindow w (withColor Green (polygon [(x, y+5*(size `div` 6)), (x+size,y+5*(size `div` 6)), (x+size,y+size), (x,y+size), (x, y+5*(size `div` 6))]))
> drawBackground :: Window -> Int -> Int -> Int -> IO ()
> drawBackground w x y size =
> drawInWindow w (withColor Cyan (polygon [(x, y), (x+size, y) , (x+size, y+size), (x, y+size), (x,y)]))
> drawSun :: Window -> Int -> Int -> Int -> IO ()
> drawSun w x y size =
> drawInWindow w (withColor Yellow (ellipse ((x+3*(size `div` 4)), y)(x+size, y+(size `div` 4))))
> drawHouse :: Window -> Int -> Int -> Int -> IO ()
> drawHouse w x y size =
> drawInWindow w (withColor Blue (polygon [(x+(size `div` 4), y+(size `div` 4)), (x+3*(size `div` 4),y+(size `div` 4)), (x+3*(size `div` 4),y+5*(size `div` 6)), (x+(size `div` 4),y+5*(size `div` 6)), (x+(size `div` 4), y+(size `div` 4))]))
> drawRuff :: Window -> Int -> Int -> Int -> IO ()
> drawRuff w x y size =
> drawInWindow w (withColor Black (polygon [(x+(size `div` 4), y+(size `div` 4)), (x+3*(size `div` 4),y+(size `div` 4)), (x+(size `div` 2), y)]))
> drawDoor :: Window -> Int -> Int -> Int -> IO ()
> drawDoor w x y size =
> drawInWindow w (withColor Black (polygon [(x+3*(size `div` 10), y+3*(size `div` 4)), (x+7*(size `div` 20),y+3*(size `div` 4)), (x+7*(size `div` 20),y+5*(size `div` 6)), (x+3*(size `div` 10),y+5*(size `div` 6)), (x+3*(size `div` 10), y+3*(size `div` 4))]))
> drawWindow :: Window -> Int -> Int -> Int -> IO ()
> drawWindow w x y size =
> drawInWindow w (withColor Cyan (polygon [(x+3*(size `div` 10), y+3*(size `div` 10)), (x+7*(size `div` 10),y+3*(size `div` 10)), (x+7*(size `div` 10),y+7*(size `div` 10)), (x+3*(size `div` 10),y+7*(size `div` 10)), (x+3*(size `div` 10), y+3*(size `div` 10))]))
Part 3: Transforming XML Documents
----------------------------------
First, a warmup:
1. Read chapters 5 and 7 of SOE.
2. Do problems 5.3, 5.5, 5.6, 7.1, and 7.2 from SOE, and turn them
is as part of the source code you create below.
Your `maxList` and `minList` functions may assume that the lists
they are passed contain at least one element.
> lengthNonRecrusive :: [a] -> Int
> lengthNonRecrusive = foldl (\a x -> (a+1)) 0
> doubleEach :: [Int] -> [Int]
> doubleEach [] = []
> doubleEach (x:xs) = (x + x) : (doubleEach xs)
> doubleEachNonRecursive :: [Int] -> [Int]
> doubleEachNonRecursive = map (\ x -> (x + x))
> pairAndOne :: [Int] -> [(Int, Int)]
> pairAndOne [] = []
> pairAndOne (x:xs) = (x, x + 1) : (pairAndOne xs)
> pairAndOneNonRecursive :: [Int] -> [(Int, Int)]
> pairAndOneNonRecursive = map (\x -> (x,x+1))
> addEachPair :: [(Int, Int)] -> [Int]
> addEachPair [] = []
> addEachPair ((a,b):xs) = (a + b) : (addEachPair xs)
> addEachPairNonRecursive :: [(Int, Int)] -> [Int]
> addEachPairNonRecursive = map (\(a,b) -> a + b)
> minList :: [Int] -> Int
> minList [] = error "ERROR: No elements in list"
> minList [x] = x
> minList (x:xs) = min x (minList xs)
> minListNonRecursive :: [Int] -> Int
> minListNonRecursive [a] = a
> minListNonRecursive (x:xs) = foldr min x xs
> maxList :: [Int] -> Int
> maxList [] = error "ERROR: No elements in list"
> maxList [x] = x
> maxList (x:xs) = max x (maxList xs)
> maxListNonRecursive :: [Int] -> Int
> maxListNonRecursive [a] = a
> maxListNonRecursive (x:xs) = foldr max x xs
> data Tree a = Leaf a | Branch (Tree a) (Tree a)
> deriving (Show, Eq)
> foldTree :: (b -> a) -> (a -> a -> a) -> Tree b -> a
> foldTree leaf branch (Leaf a) = (leaf a)
> foldTree leaf branch (Branch t1 t2) = branch (foldTree leaf branch t1) (foldTree leaf branch t2)
> fringe :: Tree a -> [a]
> fringe = foldTree (\a -> [a]) (\a1 a2 -> a1 ++ a2)
> treeSize :: Tree a -> Int
> treeSize = foldTree (\a -> 1) (\a1 a2 -> a1 + a2)
> treeHeight :: Tree a -> Int
> treeHeight = foldTree (\a -> 0) (\a1 a2 -> 1 + (max a1 a2))
> data InternalTree a = ILeaf | IBranch a (InternalTree a) (InternalTree a)
> deriving (Show, Eq)
> takeTree :: Int -> InternalTree a -> InternalTree a
> takeTree 0 t = ILeaf
> takeTree n (IBranch a t1 t2) = IBranch a (takeTree (n - 1) t1) (takeTree (n - 1) t2)
> takeTree n ILeaf = ILeaf
> takeTreeWhile :: (a -> Bool) -> InternalTree a -> InternalTree a
> takeTreeWhile f ILeaf = ILeaf
> takeTreeWhile f (IBranch a t1 t2) = if (f a)
> then IBranch a (takeTreeWhile f t1) (takeTreeWhile f t2)
> else ILeaf
Write the function map in terms of foldr:
> myMap :: (a -> b) -> [a] -> [b]
> myMap f = foldr (\x a -> (f x) : a) []
The rest of this assignment involves transforming XML documents.
To keep things simple, we will not deal with the full generality of XML,
or with issues of parsing. Instead, we will represent XML documents as
instances of the following simplified type:
~~~~
data SimpleXML =
PCDATA String
| Element ElementName [SimpleXML]
deriving Show
type ElementName = String
~~~~
That is, a `SimpleXML` value is either a `PCDATA` ("parsed character
data") node containing a string or else an `Element` node containing a
tag and a list of sub-nodes.
The file `Play.hs` contains a sample XML value. To avoid getting into
details of parsing actual XML concrete syntax, we'll work with just
this one value for purposes of this assignment. The XML value in
`Play.hs` has the following structure (in standard XML syntax):
~~~
<PLAY>
<TITLE>TITLE OF THE PLAY</TITLE>
<PERSONAE>
<PERSONA> PERSON1 </PERSONA>
<PERSONA> PERSON2 </PERSONA>
... -- MORE PERSONAE
</PERSONAE>
<ACT>
<TITLE>TITLE OF FIRST ACT</TITLE>
<SCENE>
<TITLE>TITLE OF FIRST SCENE</TITLE>
<SPEECH>
<SPEAKER> PERSON1 </SPEAKER>
<LINE>LINE1</LINE>
<LINE>LINE2</LINE>
... -- MORE LINES
</SPEECH>
... -- MORE SPEECHES
</SCENE>
... -- MORE SCENES
</ACT>
... -- MORE ACTS
</PLAY>
~~~
* `sample.html` contains a (very basic) HTML rendition of the same
information as `Play.hs`. You may want to have a look at it in your
favorite browser. The HTML in `sample.html` has the following structure
(with whitespace added for readability):
~~~
<html>
<body>
<h1>TITLE OF THE PLAY</h1>
<h2>Dramatis Personae</h2>
PERSON1<br/>
PERSON2<br/>
...
<h2>TITLE OF THE FIRST ACT</h2>
<h3>TITLE OF THE FIRST SCENE</h3>
<b>PERSON1</b><br/>
LINE1<br/>
LINE2<br/>
...
<b>PERSON2</b><br/>
LINE1<br/>
LINE2<br/>
...
<h3>TITLE OF THE SECOND SCENE</h3>
<b>PERSON3</b><br/>
LINE1<br/>
LINE2<br/>
...
</body>
</html>
~~~
You will write a function `formatPlay` that converts an XML structure
representing a play to another XML structure that, when printed,
yields the HTML specified above (but with no whitespace except what's
in the textual data in the original XML).
> appendBR :: [SimpleXML] -> [SimpleXML]
> appendBR = foldr (\x a -> [x, (Element "br" [])] ++ a) []
> formPersona :: SimpleXML -> SimpleXML
> formPersona (Element "PERSONA" [person]) = person
> formPersona xml = error "Error: not well defined!"
> formSpeech :: SimpleXML -> SimpleXML
> formSpeech (Element "SPEAKER" person) = (Element "b" person)
> formSpeech (Element "LINE" [line]) = line
> formSpeech xml = error "Error: not well defined!"
> formScene :: SimpleXML -> [SimpleXML]
> formScene (Element "TITLE" title) = [Element "h3" title]
> formScene (Element "SPEECH" speech) = appendBR (map formSpeech speech)
> formScene xml = error "Error: not well defined!"
> formAct :: SimpleXML -> [SimpleXML]
> formAct (Element "TITLE" title) = [Element "h2" title]
> formAct (Element "SCENE" scene) = (foldr (\xml html -> (formScene xml) ++ html) [] scene)
> formAct xml = error "Error: not well defined!"
> formPlay :: SimpleXML -> [SimpleXML]
> formPlay (Element "TITLE" title) = [Element "h1" title]
> formPlay (Element "PERSONAE" personas) = (Element "h2" [(PCDATA "Dramatis Personae")]) : (appendBR (map formPersona personas))
> formPlay (Element "ACT" act) = (foldr (\xml html -> (formAct xml) ++ html) [] act)
> formPlay xml = error "Error: not well defiend!"
> formatPlay :: SimpleXML -> SimpleXML
> formatPlay (Element "PLAY" xmls) = Element "html" [Element "body" (foldr (\xml html -> (formPlay xml) ++ html) [] xmls)]
> formatPlay xml = error "Error: Not well defined!"
The main action that we've provided below will use your function to
generate a file `dream.html` from the sample play. The contents of this
file after your program runs must be character-for-character identical
to `sample.html`.
> mainXML = do writeFile "dream.html" $ xml2string $ formatPlay play
> testResults "dream.html" "sample.html"
>
> firstDiff :: Eq a => [a] -> [a] -> Maybe ([a],[a])
> firstDiff [] [] = Nothing
> firstDiff (c:cs) (d:ds)
> | c==d = firstDiff cs ds
> | otherwise = Just (c:cs, d:ds)
> firstDiff cs ds = Just (cs,ds)
>
> testResults :: String -> String -> IO ()
> testResults file1 file2 = do
> f1 <- readFile file1
> f2 <- readFile file2
> case firstDiff f1 f2 of
> Nothing -> do
> putStr "Success!\n"
> Just (cs,ds) -> do
> putStr "Results differ: '"
> putStr (take 20 cs)
> putStr "' vs '"
> putStr (take 20 ds)
> putStr "'\n"
Important: The purpose of this assignment is not just to "get the job
done" --- i.e., to produce the right HTML. A more important goal is to
think about what is a good way to do this job, and jobs like it. To
this end, your solution should be organized into two parts:
1. a collection of generic functions for transforming XML structures
that have nothing to do with plays, plus
2. a short piece of code (a single definition or a collection of short
definitions) that uses the generic functions to do the particular
job of transforming a play into HTML.
Obviously, there are many ways to do the first part. The main challenge
of the assignment is to find a clean design that matches the needs of
the second part.
You will be graded not only on correctness (producing the required
output), but also on the elegance of your solution and the clarity and
readability of your code and documentation. Style counts. It is
strongly recommended that you rewrite this part of the assignment a
couple of times: get something working, then step back and see if
there is anything you can abstract out or generalize, rewrite it, then
leave it alone for a few hours or overnight and rewrite it again. Try
to use some of the higher-order programming techniques we've been
discussing in class.
Submission Instructions
-----------------------
* If working with a partner, you should both submit your assignments
individually.
* Make sure your `hw1.lhs` is accepted by GHC without errors or warnings.
* Attach your `hw1.hs` file in an email to `[email protected]` with the
subject "HW1" (minus the quotes).
*This address is unmonitored!*
Credits
-------
This homework is essentially Homeworks 1 & 2 from
<a href="http://www.cis.upenn.edu/~bcpierce/courses/552-2008/index.html">UPenn's CIS 552</a>.
module Main where
import qualified Hw1 as H
import Text.Printf
main :: IO ()
main = do
putStrLn(printf "rectangle sides: %d" (H.sides (H.rectangle 2 3)))
putStrLn(printf "rtTriangle sides: %d" (H.sides (H.rtTriangle 2 3)))
putStrLn(printf "Polygon sides with 0 vertexes: %d" (H.sides (H.Polygon [])))
putStrLn(printf "Polygon sides with 1 vertexes: %d" (H.sides (H.Polygon [(1.1, 1.1)])))
putStrLn(printf "Polygon sides with 2 vertexes: %d" (H.sides (H.Polygon [(1.1, 1.1),(1.2, 1.2)])))
putStrLn(printf "Polygon sides with 4 vertexes: %d" (H.sides (H.Polygon [(1.1, 1.1),(1.2, 1.2),(1.3, 1.3),(1.4, 1.4)])))
putStrLn(printf "Ellipse: %d" (H.sides (H.Ellipse 1.1 1.1)))
H.hanoi 2 "a" "b" "c"
H.sierpinskiCarpet
putStrLn(printf "lengthNonRecrusive []: %d" (H.lengthNonRecrusive []))
putStrLn(printf "lengthNonRecrusive [1,2,3,4]: %d" (H.lengthNonRecrusive ["1","2","3","4"]))
putStrLn(printf "doubleEach [1,2,3,4] %s" (show (H.doubleEach [1,2,3,4])))
putStrLn(printf "doubleEachNonRecursive [1,2,3,4] %s" (show (H.doubleEachNonRecursive [1,2,3,4])))
putStrLn(printf "pairAndOne [1,2,3,4] %s" (show (H.pairAndOne [1,2,3,4])))
putStrLn(printf "pairAndOneNonRecursive [1,2,3,4] %s" (show (H.pairAndOneNonRecursive [1,2,3,4])))
putStrLn(printf "addEachPair [(1,2),(2,3),(3,4),(4,5)] %s" (show (H.addEachPair [(1,2),(2,3),(3,4),(4,5)])))
putStrLn(printf "addEachPairNonRecursive [(1,2),(2,3),(3,4),(4,5)] %s" (show (H.addEachPairNonRecursive [(1,2),(2,3),(3,4),(4,5)])))
putStrLn(printf "minList [1,5,2,3,0,6,2] %s" (show (H.minList [1,5,2,3,0,6,2])))
putStrLn(printf "minListNonRecursive [1,5,2,3,0,6,2] %s" (show (H.minListNonRecursive [1,5,2,3,0,6,2])))
putStrLn(printf "maxList [1,5,2,3,0,6,2] %s" (show (H.maxList [1,5,2,3,0,6,2])))
putStrLn(printf "maxListNonRecursive [1,5,2,3,0,6,2] %s" (show (H.maxListNonRecursive [1,5,2,3,0,6,2])))
putStrLn(printf "fringe (Branch (Branch (Leaf 1) (Leaf 2)) (Leaf 3)) %s" (show (H.fringe (H.Branch (H.Branch (H.Leaf 1) (H.Leaf 2)) (H.Leaf 3)))))
putStrLn(printf "treeSize (Branch (Branch (Leaf 1) (Leaf 2)) (Leaf 3)) %s" (show (H.treeSize (H.Branch (H.Branch (H.Leaf 1) (H.Leaf 2)) (H.Leaf 3)))))
putStrLn(printf "treeHeight (Branch (Branch (Leaf 1) (Leaf 2)) (Leaf 3)) %s" (show (H.treeHeight (H.Branch (H.Branch (H.Leaf 1) (H.Leaf 2)) (H.Leaf 3)))))
let t = (let t' = (let t'' = H.IBranch 1 H.ILeaf H.ILeaf in H.IBranch 2 t'' t'') in H.IBranch 3 t' t') in do
putStrLn(printf "takeTree 0 (Branch 3 (Branch 2 (Branch 1 Leaf Leaf)) (Branch 2 (Branch 1 Leaf Leaf))) %s" (show (H.takeTree 0 t)))
putStrLn(printf "takeTree 1 (Branch 3 (Branch 2 (Branch 1 Leaf Leaf)) (Branch 2 (Branch 1 Leaf Leaf))) %s" (show (H.takeTree 1 t)))
putStrLn(printf "takeTree 2 (Branch 3 (Branch 2 (Branch 1 Leaf Leaf)) (Branch 2 (Branch 1 Leaf Leaf))) %s" (show (H.takeTree 2 t)))
putStrLn(printf "takeTree 3 (Branch 3 (Branch 2 (Branch 1 Leaf Leaf)) (Branch 2 (Branch 1 Leaf Leaf))) %s" (show (H.takeTree 3 t)))
putStrLn(printf "takeTreeWhile (> 2) (Branch 3 (Branch 2 (Branch 1 Leaf Leaf)) (Branch 2 (Branch 1 Leaf Leaf))) %s" (show (H.takeTreeWhile (>2) t)))
putStrLn(printf "myMap (\\x -> x + x) [1,2,3,4] %s" (show (H.myMap (\x -> x + x) [1,2,3,4])))
H.mainXML
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment