Seven Languages in Seven Weeks: Haskell Day 1 & 2

For the Haskell questions, I have included all the answers in a single file, one file per day. I have put the question numbers in the comments.

Here were the questions for the first day:

module Main where
	-- question 1 a
	allEven :: [Integer] -> [Integer]
	allEven [] = []
	allEven (h:t) = if even h then h:allEven t else allEven t
	
	-- question 1 b
	allEven2 :: [Integer] -> [Integer]
	allEven2 list = [x | x <- list, even x]
	
	-- question 2 
	reverseList :: [a] -> [a]
	reverseList [] = []
	reverseList (head:tail) = reverseList tail ++ [head] 

	-- question 3
	colors = ["black", "blue", "white", "yellow", "red"]
	allColors = [(a, b) | a <- colors, b <- colors, a < b]
	
	-- question 4
	multTable :: Integer -> [(Integer, Integer, Integer)]
	multTable x = [(a, x, a * x) | a <- [1..12]]
	
	-- question 5
	mapColors = ["blue", "green", "red"]
	mapColoring = [(("Tennessee", a), ("Mississippi", b), ("Alabama", c), ("Georgia", d), ("Florida", e)) 
												  | a <- mapColors, 
													b <- mapColors, 
													c <- mapColors, 
													d <- mapColors, 
													e <- mapColors,
													a /= b, a /=c, a /= d,
													b /= c,
													c /= d, c /= e,
													d /= e
													]

Again, like for day one, I have included all my answers in a single file, with comments specifying the question numbers.

module Main where
	-- question 1
	sort :: [Integer] -> [Integer]
	sort [] = []
	sort list = [minimum list] ++ sort [x | x <- list, x /= minimum list]
	
	-- question 2
	sortWith [] f = []
	sortWith list f = [f list] ++ sortWith [x | x <- list, x /= f list] f
	
	-- question 4
	everyThird x = x:(everyThird (x + 3))
	everyFifth y = y:(everyFifth (y + 5))
	everyEigth x y = zipWith (+) (everyThird x) (everyFifth y)
	
	-- question 5
	prod a b = a * b
	halfOf = prod 0.5  

	-- question 6
	appendToString s a = a ++ s
	addNewLine = appendToString "\n"
	
	-- bonus question 1
	biggestCommonDenominator :: Integer -> Integer -> Integer 
	biggestCommonDenominator a 0 = a
	biggestCommonDenominator a b = biggestCommonDenominator b (mod a b)

Seven Languages in Seven Weeks: Clojure Day 2

Here are the questions for day two:

Using macros and an else condition implement an unless function.

(ns day2q1)

(defmacro unless [test body]
  (list 'cond (list '= true test) (println "") :else body))

(unless true (println "Danger, danger Will Robinson"))
(unless false (println "Do not underestimate the power of the dark side!"))

Using defrecord, write a type that implements a protocol.

(ns day2q2)

(defprotocol Dragon
  (breath [this])
  (fly [this where]))

(defrecord RedDragon [name] 
  Dragon
  (breath [this] (println "Red dragon breathes fire!"))
  (fly [this where] (println "Fly to " where)))

(def Verminthrax (RedDragon. "Verminthrax"))

(breath Verminthrax)
(fly Verminthrax :mystara)

Seven Languages in Seven Weeks: Clojure Day 1

Up until now, I have programmed the solutions for the Seven Seven Languages in Seven Weeks questions using a simple text editor, Scribes, and running them in the console.

If you use Linux and a WM that runs GTK, I suggest giving Scribes a spin. It has a minimalist interface that gets out of your way and offers many keyboard shortcuts (press Ctr-H for help on shortcuts). If you run on Ubuntu, consider installing it from a PPA package, as the Ubuntu version (at the time of this writing, in 10.04 LTS) is, to quote Scribes website:

It’s old, buggy and unsupported!

The reason I had been using a simple set up was to avoid having to learn new IDEs and the like for each language and concentrate simply on the code. Plus there is something to be said for such a setup when you just want to quickly get coding at home.

With Clojure, you have to do some project setup. For this, the book suggests using Leiningen which is a powerful and popular tool for working with Clojure projects.

Rather than use Leiningen to start my project and then use Scribes afterwards, I found it was easier to use an IDE, Eclipse, and use a Clojure plugin, CounterClockWise. Your mileage may vary, but if you are starting the Clojure chapter, I recommend trying CounterClockWise.

Here were the questions:

Write a function that returns whether a string is longer than n characters.

(ns day1q1)

(defn big [st n] (> (count st) 4))

(big "This is a test" 4)

Write a function that returns the correct collection type from amongst the following :list, :map:, :vector.

(ns day1q2)

(defn collection-type [col] 
   (cond
     (list? col) :list
     (map? col) :map
     (vector? col) :vector))

(collection-type [:hutt :wookie :ewok])
(collection-type (list 1 2 3))
(collection-type {:chewie :wookie :lea :human})

As for Clojure itself, it’s a dialect of Lisp that runs on the JVM. If you did not know, programming in Lisp gives you instant geek cred.

Jokes aside, I was inspired to learn new languages, and to read Seven Seven Languages in Seven Weeks by a famous article entitled the Beating the Averages, which is mostly about Lisp. If you don’t want to read the whole thing, consider at least reading through The Blub Paradox part. This part is very thought provoking.

Along with What Is Software Design?, Beating the Averages (for it’s Blub Paradox) are the two articles/blog entries that I would recommend every developer should read.

Seven Languages in Seven Weeks: Erlang Day 1 & 2

The next language in the book was Erlang. Before I give my answers for the first two days of Erlang, I will introduce the language itself.

Erlang was initially developed by Ericsson. It is specifically attributed to Joe Armstrong. The name can stand for Ericsson Language or danish mathematecian’s Agner Erlang name.

Some of the features of the language include a powerful concurrency model, hot swapping of modules and the ability to easily monitor and restart modules. Even without taking these features into consideration, the language offers an interesting proposition for programmers.

Erlang is one of the languages in the book to which I took a particular liking. I like the syntax and how the functional nature of the language is expressed.

The syntax borrows from Prolog, which is a good thing in my book. The programming model on the other hand, is nothing like Prolog.

Here are my answers to the questions for Erlang’s first chapter.

Using recursion, write a function that counts the number of words in a string.

% Erland Day 1 Q 1

-module(day1q1).
-export([number_of_words/1]).

number_of_words(S) -> number_of_words_recursive(string:tokens(S, " ")).

number_of_words_recursive([]) -> 0;
number_of_words_recursive(S) -> [Head | NewList] = S,
								1 + number_of_words_recursive(NewList).

Count to ten using recursion.

% Erlang day 1 q 2

-module(day1q2).
-export([count_to_ten/0]).

count_to_ten() -> count_to_ten(1).
count_to_ten(10) -> io:write(10);
count_to_ten(I) -> io:write(I),
				   count_to_ten(I + 1).
				   

Use matching to either print “success” or “error: ” accompanied with a specified error message. The function must take an input of the form: {error, Message}.

% Erlang day1 q 3

-module(day1q3).
-export([error_or_success/1]).

error_or_success(success) -> io:fwrite(success);
error_or_success({error, Y}) -> io:fwrite(error),
						    io:fwrite(":"),
						    io:fwrite(Y).

And now here are my solutions for Seven Seven Languages in Seven Weeks Erlang Day 2 chapter.

Write a function that takes a list of key-value tuples and a key. The function must return the associated value.

-module(day2q1).
-export([test/2]).

print_value(Value) -> io:format("~p~n", [Value]).

test(List, Keyword) -> [print_value(Value) || {Key, Value} <- List, Key =:= Keyword].

Write a function that uses a list comprehension to transform a list of the form [{item, quantity, price}, …] into the form [{item total_price}, …].

-module(day2q2).
-export([price/1]).

price(List) -> [{Item, Quantity * Price} || {Item, Quantity, Price} <- List].

Example usage:

6> day2q2:price([{book, 2, 4}, {tootbrush, 5, 5}]).
[{book,8},{tootbrush,25}]

And now, the bonus question…

Write a program that takes a Tic Tac Toe board in the form of a tuple of size nine. Return the winner or lack of thereof (cat).

In an earlier post, I mentioned a Tic Tac Toe solver I had came up with, and how I had found a better solution. Well here it is.

I found this approach a lot simpler than what I did in Scala. The code is twenty one lines, three of which are white spaces and another three which are comments. So fifteen lines total.

-module(day2q3).
-export([tic_tac_toe/1]).

%WinningPaths = [{1, 2, 3}, {4, 5, 6}, {7, 8, 9},
%				{1, 4, 6}, {2, 5, 8}, {3, 6, 9},
%				{1, 5, 9}, {7, 5, 3}].

tic_tac_toe({Z, Z, Z, _, _, _, _, _, _}) -> io:format("Winner: ~p~n", [Z]);
tic_tac_toe({_, _, _, Z, Z, Z, _, _, _}) -> io:format("Winner: ~p~n", [Z]);
tic_tac_toe({_, _, _, _, _, _, Z, Z, Z}) -> io:format("Winner: ~p~n", [Z]);
tic_tac_toe({Z, _, _, Z, _, _, Z, _, _}) -> io:format("Winner: ~p~n", [Z]);
tic_tac_toe({_, Z, _, _, Z, _, _, Z, _}) -> io:format("Winner: ~p~n", [Z]);
tic_tac_toe({_, _, Z, _, _, Z, _, _, Z}) -> io:format("Winner: ~p~n", [Z]);
tic_tac_toe({Z, _, _, _, Z, _, _, _, Z}) -> io:format("Winner: ~p~n", [Z]);
tic_tac_toe({_, _, Z, _, Z, _, Z, _, _}) -> io:format("Winner: ~p~n", [Z]);

tic_tac_toe(List) -> Empty_Squares = lists:any(fun(X) -> X == ' ' end, tuple_to_list(List)), 
					 if  
						Empty_Squares == true -> io:format("No winner. ~n");
						Empty_Squares == false -> io:format("cat ~n")
					 end.

Basically, this is very similar to how I would solve the problem in Prolog. First I define all the winning scenarios, then I handle the two other cases.

Of course, this approach still has a couple of problems. It does not validate the board in any way. I can see multiple ways to break this by sending invalid boards (ie: a full board made up only of X). Also it treats empty spaces as a player.

In a full Tic Tac Toe game, I would ensure that the function that updates the board cannot send it in an invalid state and also validate the consistency of board in regards to the rules of Tic Tac Toe.