Monday, June 25, 2012

On Lisp in Clojure chapter 11 (11.3 - 11.6)

I am continuing to translate the examples from On Lisp by Paul Graham into Clojure. The examples and links to the rest of the series can be found on github.

Section 11.3 Conditional Evaluation

Graham makes such a great point in this section that I wanted to start with it: "When faced with a choice between a clean idiom and an efficient one, we go between the horns of the dilemma by transforming the former into the latter."

I decided to write Graham's if3 macro using true, false and nil for 3 value truthiness. Normally in an if statement nil and false are evaluated the same. The nif macro, is very similar. In the Clojure form, the test is evaluated in a let binding, so that it only has to be evaluated once.

(defmacro if3 [test t-case nil-case f-case]
  `(let [expr# ~test]
     (cond
      (nil? expr#) ~nil-case
      (false? expr#) ~f-case
      :default ~t-case)))

(defmacro nif  [expr pos zero neg]  `(let [expr# ~expr]
    (cond
     (pos? expr#) ~pos
     (zero? expr#) ~zero
     :default ~neg)))

Graham presents us with an `in` macro which tests for membership using a series of tests of equality joined in an or expression.

(defmacro in? [needle & haystack]  ( let [target# needle]
    `(or ~@(map (fn [x#] `(= ~x# ~target#)) haystack))))

(macroexpand-1
 '(in? 1 1 2 3))

;;(clojure.core/or (clojure.core/= 1 1) (clojure.core/= 2 1) (clojure.core/= 3 1))


;; Just to make sure it is working the way we hope
(in? 1 1 (do (println "called") 2) 3)

The Clojure function `some` uses `or` recursively to find the first match.

Clojure's lazy sequences provide another way to get the same functionality. The member? function below returns the first match in the sequence. The argument list is different in this implementation because i wanted the caller to pass a collection, rather than several elements that I wrap in to a collection, because this allows me to work with an infinite collection, such as all positive integers.

;; lazy function
(defn member? [needle haystack]
  (take 1 (filter (partial = needle) haystack)))

(member? 2 (iterate inc 1) )

in-f is almost the same as in?, except that it allows us to pass the function to use for the comparison.

(defmacro in-if [func needle & haystack]
  (let [target# needle]
    `(or ~@(map (fn [x#] `(~func ~x# ~target#)) haystack))))

Graham creates a >case macro that applies a case statement with expressions as keys instead of constants. Each key will be evaluated until a match is found. Once a match is found, no more keys will be evaluated. Clojure's cond statement already behaves like that.

(cond
 (do (println "First cond") false) (println "one")
 (do (println "Second cond") true) (println "two")
 (do (println "Third cond") true) (println "three")
 :default (println "Nothing matched"))

Section 11.4 iteration

Clojure's partition function makes breaking the source parameter into chunks pretty easy. Of course, partition makes the macro easier, it also makes for a short inline invocation. Here is do-tuples-o, followed by an example call to the macro, and an example of writing the map expression directly.

(defmacro do-tuples-o [parms source & body]
  (let [src# source]
    `(map (fn [~parms] ~@body)
          (partition (count (quote ~parms)) 1 ~src#))))

(do-tuples-o [x y] [1 2 3 4 5] (+ x y))

(map
     (fn [[x y]] (+ x y))
     (partition 2 1 [1 2 3 4 5]))

If we use partition in conjunction with cycle, we can create our parameter list that wraps around. The only change we have to make for do-tuples-c is to change partition to partition-round. I also changed my sample call, to show it can work with a function of any arity.

(defn partition-round [size step source]
  (partition size step
             (take (- (+ size (count source)) step)
                   (cycle source))))
(defmacro do-tuples-c [parms source & body]
  (let [src# source]
    `(map (fn [~parms] ~@body)
          (partition-round (count ( quote ~parms)) 1 ~src#))))

(do-tuples-c [x y z] [1 2 3 4 5] (+ x y z))

(map
     (fn [[x y z]] (+ x y z))
     (partition-round 3 1 [1 2 3 4 5]))

Section 11.5 Iteration with Multiple Values

In this section, Graham shows us a macro that executes a do loop that increments several variables in parallel and allows for multiple return values. He then shows us an example of a game that might use this sort of construct to track moving objects.

Multiple return values in a list based language really seems like a non-issue to me.

The sample game that Graham describes looks interesting. I hope to do a Clojure implementation of it soon, and then I will have a better context to evaluate the need for a multi-varibale do.

Section 11.6 Need for Macros

In earlier sections, Graham described using macros for conditional evaluation and iteration. Here he shows us how the some of the same things can be done with functions.

(defn fnif [test then else]
  (if test (then) (else)))

(fnif true (fn [] (do (println "true") (+ 1 2))) (fn []  (do (println "false")  (- 2 1))))

(defn forever [fn]
  (if true
    (do
      (fn)
      (recur fn))
    'done))

#_(forever (fn [] (println "this is dumb")))

We have to wrap the code we want executed within an anonymous function which we invoke when we want the code evaluated. Graham points out that in these situations, the macro solution is much cleaner, if not strictly necessary. He also says simple binding situations can be handled with map, but that more complicated situations are only possible with macros.

Tuesday, June 5, 2012

On Lisp in Clojure chapter 11 (section 11.2)

I am continuing to translate the examples from On Lisp by Paul Graham into Clojure. The examples and links to the rest of the series can be found on github.

I am only covering one section in this post, but this one section includes file I/O, exception handling and locking. This is a post about the examples from On Lisp, and so isn't a tutorial on any of these topics. Hopefully, it provides a gentle introduction to each topic.

Section 11.2 The with- macro

The with-open-file macro Graham describes is just with-open in Clojure. It can be used with any resource that implements a close method.

(with-open [writer (clojure.java.io/writer "output-file" :append true)]
  (.write writer "99"))

Clojure has a pair of functions for doing stream I/O. slurp and spit, for reading and writing, both use with-open to manage their streams.

(spit "output.txt" "test" :append true )
(slurp "output.txt")

Graham's unwind-protect becomes a try-catch-finally block, which works just like you would expect.

(try
  (do (println "What error?")
      (throw (Exception. "This Error."))
      (println "This won't run"))
  (catch Exception e (.getMessage e))
  (finally (println "this runs regardless")))

Graham's with-db example combines mutations, locks and exception handling. In his first example, he rebinds *db* to a new value, locks it, uses the new value, releases the lock and resets the value. In Clojure, you can create dynamic variables, but changes to their values only appear in the current thread. For Clojure datatypes locks are unnecessary.

(def ^:dynamic *db* "some connection")

(binding [ *db* "other connection"]
         (println *db*))

Because the value assigned to a var with binding is only visible on the current thread, this will not work with code that you want to execute on a different thread. If we are using mutable Java objects across different threads, locking can come into play. Clojure has a locking macro which accepts the object to lock and the code to be executed.

Strings in Java are immutable, so I am going to use a StringBuilder. Graham's let form becomes something like this:

(def db2 (StringBuilder. "connection"))

(let [old-val (.toString db2)]
  (.replace db2 0 (.length db2) "new connection")
  (locking db2
    (println (.toString db2)))
  (.replace db2 0 (.length db2) old-val))

Clearly Graham's call to with-db is preferable to writing the let form over and over. And, as he points out, it is easy enough to add a try-finally block to make a safer implementation.

(defmacro with-db [db & body]
  `(let [temp# (.toString db2)]
    (try
      (.replace db2 0 (.length db2) ~db)
      (locking db2
        ~@body)
      (finally
       (.replace db2 0 (.length db2) temp#)))))

(with-db "new connection"
   (println (.toString db2)))

Graham also gives an example that uses both a macro and a function, which has most of the work being done in the function inside of a context created by the macro. I am not going to claim to understand how Common Lisp manages memory, or how that is different from Clojure. Instead, I will simply acknowledge his point, that perhaps a macro can be used to create a context, and the rest of the work can be done in a function.

Friday, May 25, 2012

On Lisp in Clojure chapter 11 (section 11.1)

I am continuing to translate the examples from On Lisp by Paul Graham into Clojure. The examples and links to the rest of the series can be found on github.

Normally I would cover more than just 1 section in a post, but I thought material in this section could stand to be in its own discussion. In addition, the next section has so much in it that it will need its own post.

Section 11.1 Creating Context

The call to let is included for completeness. I thought the definition of our-let was pretty neat. I think it shows pretty clearly what Graham means when he talks about using a macro to create a context.

(let [x 'b] (list x))

(defmacro our-let [binds & body]
  `((fn [~@(take-nth 2 binds)]
       (do ~@body)) ~@(take-nth 2 (rest binds))))

(macroexpand-1 '(our-let [x 1 y 2] (+ x y)))
;; ((clojure.core/fn [x y] (do (+ x y))) 1 2)

(our-let [x 1 y 2] (+ x y))
;; 3

It seems like we get to see the when macro every chapter. It looked to me like the when-bind* was dropping all its variables, so clearly I don't understand it to translate it. In Clojure, gensym is done by appending # to any variable that you name in a macro.

(defmacro when-bind [[var expr] & body]
  `(let [~var ~expr]
     (when ~var
       ~@body)))

Graham showed us a cond-let function that accepted a sequence of pairs containing a boolean expression followed by a let binding. In Graham's implementation he had two helper functions and one macro. I wrote it with one helper function that recursively walks through the boolean expressions until it finds one that is true.

(defn condlet-bind [bindings]
  (loop [binds bindings]
    (cond (empty? binds) []
          (first binds) (first (rest binds))
          :default (recur (rest (rest binds))))))

(defmacro condlet [clauses & body]
  `(let ~(condlet-bind clauses)
     ~@body))

I want to point out the difference between this `condlet` function and Clojure.core's `if-let` function. condlet takes a list containing booleans and bindings, and will apply the first binding for which the boolean is true. if-let says if an expression is true, bind it to a symbol and execute one branch of code; if it is not true don't bind anything, and take a different branch.

In the following pseudo code, if some-expression returns a value other than false or nil, x gets bound to the result and do-something is called. If some-expression evaluates to false or nil, x does not get bound to anything and do-something-else gets called, just like a normal if.

#_(if-let [x (some-expression)]
  (do-something x)
  (do-something-else))

Tuesday, May 22, 2012

Functional Tic-Tac-Toe

Recently in the #Clojure channel on Freenode I heard someone say that you could write a tic-tac-toe game without any mutable variables. I had trouble conceiving how that could be possible. I decided to write one to find out.

The full running code is on github. This post will just look at a few of the functions that show how what seems like such an imperative problem can be solved in a functional way.

When I first created the project, I called it stateless-tic-tac-toe, but this was a misnomer. There is state everywhere. Each of the functions get passed the state they need to operate on, and usually the return is an updated version of the state.

Writing individual functions was pretty straight forward. I knew I was going to need a function that took no parameters and returned an empty board. It didn't take me long to realize that I would need to keep track of who's turn it was also.

(defn new-game [] 
  [(into [] (map str (range 1 10))) "X"])

The first big difference between a functional implementation and an imperative one is in the move function. In an imperative version, the board would be stored in a variable or property, and move would be a method that accepted a move as a parameter and modified the board variable.

In the functional version, move will not modify anything. The state of the game is passed in to move, along with the move to be applied. If the move legal, move returns a new version of the board. If the move was illegal then the calling function will get an unmodified board returned.

(defn move [[board player :as game] move]
  (if (legal-input? move)
    (let [board-index (- (Integer/parseInt move) 1)]
      (if (= (nth board board-index) move)
        [(assoc board board-index player)
         (if (= player "X") "O" "X")] 
        game)) game))

Functions like check-winner again show the different style of functional verses imperative. check-winner is passed in the current game state. It passes the current board configuration to functions that check for horizontal, vertical and diagonal lines. Finally, it returns the winner if there is one, or nil, which is evaluated to false, if there is no winner.

(defn check-winner [[board _]]
  (first (concat (check-horizontal board)
                 (check-vertical board) 
                 (check-diaganal board))))

I used a text based UI, which is pretty straight forward. Drawing the board is done with a function that takes in the board vector and returns strings that can be printed out to show the board. Everything was going great until I was ready for the actual event loop.

Using a while loop seemed like such a natural way to structure the game. While the game is not over, redraw the board and ask for a new move. I couldn't find a good way to write that without mutation. Instead of a while loop, I needed to use recursion.

Once I realized that I needed recursion, the function came pretty quickly. I have a function that takes in the game state and draws the board. After that, it checks to see if the game is over. If someone has won the game, or there are no more legal moves, the function prints out a message, and then exits. If the game is not over yet, the play-game function calls the move function and recursively calls itself with the result.

(defn play-game [the-game]
  (loop [game the-game]
    (println (render-board game))
    (if (game-over? game)
          (if-let [winner (check-winner game)]
            (println (str "Congrats to " winner))
            (println "tie game"))
          (recur (move game (get-move))))))

Wednesday, May 16, 2012

On Lisp in Clojure, chapter 10

I am continuing to translate the examples from On Lisp by Paul Graham into Clojure. The examples and links to the rest of the series can be found on github.

Chapter 10 presented some interesting problems. Some of them were the result of rampant mutability, and I have skipped those, but much of the rest applies to Clojure.

Stuart Halloway also has written a post on this chapter on his blog.

Section 10.1 Number of Evaluations

The difference between the correct version of the for loop and the multiple evaluation version is pretty straight forward. By binding ~stop to gstop#, stop only gets evaluated once.

;; correct version
(defmacro for' [[var start stop] & body]
  `(let [~var (atom ~start) gstop# ~stop]
     (while (< (deref ~var) gstop#)
         ~@body
         (swap! ~var inc))))

;; subject to multiple evaluations
(defmacro for' [[var start stop] & body]
  `(let [~var (atom ~start)]
     (while (< (deref ~var) ~stop)
       ~@body
       (swap! ~var inc))))

The the problem with the last version of the for loop really belongs in the next section.

;; incorrect order of evaluation
(defmacro for' [[var start stop] & body]
    `(let [gstop# ~stop ~var (atom ~start)]
       (while (< (deref ~var) ~stop)
         (swap! ~var inc)
         ~@body)))

Section 10.2 Incorrect Order of Evaluation

When I read the for macro labeled as having the incorrect order of evaluation, I thought Graham meant that the counter was being incremented at the top of the loop, and so I wrote my loop that way, and thought it was kind of a silly example. Then I tried the call to for in this section. First, Graham shows us an example where the order of evaluation gives an interesting result.

(def x (atom 10))
(+ (reset! x 3) @x)
;; => 6

In the version of the for loop with the incorrect order of evaluation, the stop variable appears first, so that gets evaluated, which sets x to 13. Then, start gets bound to the value of x, which is now 13, so the loop never actually runs. In the correct version of the for loop, in the let expression, the start is bound first, to 1, and then stop is bound to 13. I think Graham is right when he says that a caller has a right to expect start to be evaluated before stop because they appear left to right in the argument list. He is definitely right when he says this is a pathological way to call for'.

(let [x (atom 1)]
  (for' [i @x (reset! x 13)]
        (println @i)))

Section 10.3 Non-functional Expanders

This section shows a lot of awful things that can happen when you mix macros and mutation. But since we are in Clojure, we already avoid mutation when possible. Moving on...

Section 10.4 Recursion

Graham shows us how write a function with recursion and then shows us how to rewrite the same function in a more imperative manner. He does this because in this section he shows a potential pitfall of recursion in macros, and the imperative loop is an alternative.

The imperative version of our-length is a little extra painful in Clojure. Rather than mutating the list and the counter in a while loop, I am going to stick with the recursive function. We will just be careful when we recurse in macros.


(defn our-length [x]
  (loop [lst x acc 0]
    (if (empty? lst) acc
        (recur (rest lst) (inc acc)))))

Graham's ntha function works just fine. Rewriting it as the macro, nthb causes an infinite loop in the macro expansion.

 
(defn ntha [n lst]
  (if (= n 0)
    (first lst)
    (ntha (- n 1) (rest lst))))

(defmacro nthb [n lst]
  `(if (= ~n 0)
     (first ~lst)
     (nthb (- ~n 1) (rest ~lst))))

(macroexpand-1 '(nthb 2 [1 2 3 4 5]))
Graham shows a couple of ways to rewrite nth as a macro that doesn't lead to an infinite loop. I have just rewritten the version with the recursion in the macro.
(defmacro nthe [n lst]
  `(loop [n# ~n lst# ~lst]
     (if (= n# 0)
       (first lst#)
       (recur (dec n#) (rest lst#)))))

Graham also presents a pair of examples of writing a an `or` macro that sidestep the pitfalls of a recursive macro. In the first, the macro calls a recursive function. The second macro does its own recursion. This seems to be less difficult to do safely in Clojure, because recursion is done with `recur` rather than a function calling itself by name.

(defn or-expand [args]
  (if (empty? args)
    nil
    (let [sym (first args)]
       (if sym
         sym
         (or-expand (rest args))))))

(defmacro ora [& args]
  (or-expand args))

(defmacro orb [& args]
  (loop [lst args]
    (if (empty? lst) false
        (let [sym (first lst)]
          (if sym sym (recur (rest lst)))))))

Sunday, May 13, 2012

On Lisp in Clojure chapter 9

I am continuing to translate the examples from On Lisp by Paul Graham into Clojure. The examples and links to the rest of the series can be found on github.

Chapter 9 is presented for the sake of completeness. Clojure's let bindings solve most of the problems Graham describes in this chapter. You can solve the rest of the problems by putting a # at the end of any variable name you don't want to be subject to capture. e.g. x#.

Stuart Halloway also has written a post on this chapter on his blog. He gives a good description of how these capture issues relate to Clojure.

Section 9.1 Macro Argument Capture

We can write Clojure macros that run into some the same argument capture problems.

(defmacro for' [[var start stop] & body]
  `(do
     (def ~var (atom ~start))
     (def limit ~stop)
     (while (< (deref ~var) limit)
       ~@body
       (swap! ~var inc))))

;; seems to work
(for' [ x 1 10] (println (str "current value is " @x)))

;; fails with error
(for' [ limit 1 10] (println (str "current value is" @limit)))

The version that is supposed to fail silently actually works just fine.

(let [limit 5]
  (for' [i 1 10]
        (when (> @i limit)
          (println (str @i) ) )))

Section 9.2 Free Symbol Capture

Translating the examples from this section does not lead to the same errors. The w referred to in simple-ratio is different from the w referred to in gripe. I don't know why the gripe macro doesn't get fooled by the parameter in simple-ratio, but it doesn't.

(def w (atom []))

(defmacro gripe [warning]
  `(do (swap! w #(conj % (list ~warning)))
       nil))

(defn simple-ratio [v w]
  (let [vn (count v) wn (count w)]
    (if (or (< vn 2) (< wn 2))
      (gripe "sample < 2")
      (/ vn wn))))

Section 9.3 When Capture Occurs

The first couple of code snippets just show let binding to describe the free variables. The first capture example is almost identical in Clojure.

(defmacro cap1 []
  `(+ x 1))

The next several capture examples don't apply in Clojure. Even if you do have an x defined in your environment, this macro won't compile:

(defmacro cap2 [var]
  `(let [x 2 ~var 3]
     (+ x ~var)))

When the macro expands, x gets expanded to a namespace qualified symbol, such as user/x, but you can't use let to bind a value to a namespace qualified symbol. In the first example from this chapter, the for loop, I used def to bind my variables, because I wanted to go out of my way to get the error.

The only way to define a cap2 macro in Clojure is like this:

(defmacro cap2 [var]
  `(let [x# 2 ~var 3]
     (+ x# ~var)))

The # symbol after the variable name causes the macro expansion to do a gensym, which will give a unique name to x#, which no doubt is how Graham will have us solve the problem, after he finishes warning us about it.

Section 9.4 Avoiding Capture with Better Names

This section doesn't give any examples.

Section 9.5 Avoiding Capture by Prior Evaluation

The failing call to before doesn't fail in Clojure. Even with the caller using def from within a do block. Probably this is because we can't bind to a namespace qualified symbol in a let. Oh, don't call my position function on a value that doesn't exist in the sequence.

(defn position [needle haystack]
  (loop [acc 0 lst haystack]
    (cond (empty? lst) nil
          (= needle (first lst)) acc
          :default (recur (inc acc) (rest lst)))))


(defmacro before [x y seq2]
  `(let [seq# ~seq2]
     (< (position ~x seq#)
        (position ~y seq#))))

(before (do (def seq2 '(b a)) 'a) 'b '(a b))

Here is the Clojure version of the new improved for loop. Graham defined the code to be executed as a lambda, and then looped over the invocation of that function. I am just going to bind my end value as limit# and move on.

(defmacro for' [[var start stop] & body]
  `(let [~var (atom ~start) limit# ~stop ]
     (while (< (deref ~var) limit#)
       ~@body
       (swap! ~var inc))))

Sections 9.6 and 9.7

We have seen the for loop several times, and we have already mentioned that gensym in CLISP is done with appending a # to the var name. Clojure is broken up into namespaces, not packages. Namespaces make name collisions less common, but not impossible, just as Graham describes for Lisp.

Section 9.8 Capture in Other Name Spaces

I wasn't able to reproduce the error in Clojure. What mac thinks is fun is different than what my let binding does for fun.

(defn fun [x] (+ x 1))

(defmacro mac [x] `(fun ~x))

(mac 10)

(let [fun  (fn [y] (- y 1))]
  (mac 10))

Section 9.9 Why Bother

Graham's answer to the question is a good one. And Rich Hickey's implementation of Lisp solves a lot of the problems for us.

Monday, May 7, 2012

On Lisp in Clojure chapter 8

I am continuing to translate the examples from On Lisp by Paul Graham into Clojure. The examples and links to the rest of the series can be found on github.

The first two sections of chapter 8 contain a lot of discussion and only a couple of small examples. Section 8.3 is a lot more involved, and I think we do get the first suggestion that maybe macros really are as powerful as those who already know Lisp would have us believe.

Section 8.1 When Nothing Else WIll Do

Graham describes 7 situations in which macros can do things that functions cannot. The text is very informative. The examples aren't significant, but for the sake of completeness:

(defn addf [x]
  (+ x 1))

(defmacro addm [x]
  `(+ 1 ~x))

(defmacro our-while [test & body]
  `(if ~test
     (do
       (swap! ~test not)
       ~@body)))

(defmacro foo [x]
  `(+ ~x y))

Section 8.2 Macro or Function

Graham has a list of 7 points in this section too. This time it is the pros and cons of using a macro instead of a function in a situation when either will do. Interestingly, there are 3 pros and 4 cons.

(defn avg [& args]
  (/ (apply + args) (count args)))

(defmacro avgm [& args]
  `(/ (+ ~@args) ~(count args)))

((fn [x y] (avgm x y)) 1 3)

Section 8.3 Applications for Macros

nil! is different in Clojure, because most values are immutable. Mutable values may be one of several types, each of which has its own semantics. Last chapter, we did one macro to set a ref to nil and another to set an atom to nil. There may indeed be situations where you want to have the same command to change either a ref or an atom.

(defmacro nil! [x]
  `(cond (instance? clojure.lang.Atom ~x ) (reset! ~x nil)
         (instance? clojure.lang.Ref ~x) (dosync (ref-set ~x nil))))

These two equivelent definitions of foo show how the defn macro works in Clojure.

(defn foo [x] (* x 2))
(def foo (fn [x] (* x 2)))

And of course, we can write a simplistic defn macro.

(defmacro our-defn [name params & body]
  `(def ~name
     (fn ~params  ~@body)))

The last set of examples is much more involved. Graham describe a CAD system and shows how a move function and a scale function might be written.

Graham did not provide an implementation for redraw or bounds, but we need both, if our code is going compile and run.

(defn redraw [from-x from-y to-x to-y]
  (println (str "Redrawing from: " from-x "," from-y " to "
                to-x "," to-y)))

(defn bounds [objs]
  (list
   (apply min (for  [o ( :objects objs)]
                (deref  (:obj-x o))))
   (apply min (for  [o ( :objects objs)]
                (deref  (:obj-y o))))
   (apply max (for  [o ( :objects objs)]
                (+  (deref  (:obj-x o)) (deref (:obj-dx o)))))
   (apply max (for  [o ( :objects objs)]
                (+  (deref  (:obj-y o)) (deref (:obj-dy o)))))))

The move-objs and scale-objs functions take in a collection of objects that contain their x and y coordinates and their sizes. Each of the objects keep their properties in a map, because I prefer named parameters to positional ones. Each of the functions walks through the objects and transforms them. Then the redraw function is called, to redraw the affected portion of the screen.

(defn move-objs [objs dx dy]
  (let [[x0 y0 x1 y1] (bounds objs)]
    (doseq [o (:objects objs)]
      (swap! (:obj-x o) + dx)
      (swap! (:obj-y o) + dy))
    (let [[xa ya xb yb] (bounds objs)]
      (redraw (min x0 xa) (min y0 ya)
               (max x1 xb) (max y1 yb)))))

(defn scale-objs [objs factor]
  (let [[x0 y0 x1 y1] (bounds objs)]
    (doseq [o (:objects objs)]
      (swap! (:obj-dx o) * factor)
      (swap! (:obj-dy o) * factor))
    (let [[xa ya xb yb] (bounds objs)]
      (redraw (min x0 xa) (min y0 ya)
              (max x1 xb) (max y1 yb)))))

I wrote a sample collection of objects that could be passed in as obis to either function. The collection is actually a map, with all of the objects mapped to :objects. Originally, I had a keyword :bounds that stored the starting bounds of the objects, but the bounds need to be recalculated after the transformation, so it didn't make sense to store it in the collection. In the real world, the collection may have other properties aside from just the objects it contains, so I decided to leave it as a map.

(def sample-object-collection
  {:objects [{:name "Object 1"
              :obj-x (atom 0) :obj-y (atom 0)
              :obj-dx (atom 5) :obj-dy (atom 5)}
             {:name "Object 2"
              :obj-x (atom 10) :obj-y (atom 20)
              :obj-dx (atom 20) :obj-dy (atom 20)}]})

(move-objs sample-object-collection 5 5)

Both functions apply their transformations and then call the redraw function in the same verbose way. If we added a flip method and a rotate method, again we would have a unique transformation followed by the same call to redraw. To battle this repetition, Graham provides the with-redraw macro.

(defmacro with-redraw [varname objs & body]
  `(let [[x0# y0# x1# y1#] (bounds ~objs)]
     (doseq [~varname (:objects ~objs)] ~@body)
    (let [[xa# ya# xb# yb#] (bounds ~objs)]
      (redraw (min x0# xa#) (min y0# ya#)
              (max x1# xb#) (max y1# yb#)))))

Because of this macro, the new versions of move-objs and scale-objs are much nicer. Each function has gone from 8 lines to 4, and all of the code that was taken out was noisy and distracting. Now it is easy to see how each function performs its transformation.

(defn move-objs [objs dx dy]
  (with-redraw o objs
    (swap! (:obj-x o) + dx)
    (swap! (:obj-y o) + dy)))

(defn scale-objs [objs factor]
  (with-redraw o objs
    (swap! (:obj-dx o) * factor)
    (swap! (:obj-dy o) * factor)))

Thursday, May 3, 2012

On Lisp in Clojure chapter 7 (7.5 - 7.11)

I am continuing to translate the examples from On Lisp by Paul Graham into Clojure. The examples and links to the rest of the series can be found on github.

This post covers the second half of chapter 7. Stuart Halloway also has a post on this chapter on his blog.

Section 7.5 Destructuring in Parameter Lists

Clojure also has destructuring in the same form as Graham describes in Common Lisp. Clojure also supports destructuring with its map collection type. The book Clojure Programming shows how to combine vector destructuring and map destructuring in a parameter list or let binding. But back to the example...

(let [[x [y] & z] ['a ['b] 'c 'd ]]
  (list x y z))

In the next example, Graham shows a function called dolist which executes a particular function against each member of a list in succession. This may sound like map, but map builds a new list from the return values generated by applying a function to the members of a list. dolist executes a function against each member of a list and disregards the return values. It is used to execute a function for its side effects. Clojure's version is called doseq.

(doseq [x '(1 2 3)]
  (println x))

Graham then shows a way to implement a version of dolist. He builds a macro that takes in a list, a return value and the body of commands to be executed. I like the example, especially because it shows how to incorporate an optional parameter (return) and a variadic parameter (body) in the same parameter list.

The Clojure example doesn't work quite the same though. map in Clojure is lazy, the terms will only be evaluated when they are used. So if you don't pass a return value the map executes, because the reader wants to print out the return values. If you do pass a parameter, that becomes the only return value the repl needs to display, so the mapped function is never executed.

(defmacro our-dolist [[lst & result] & body]
  `(do  (map ~@body ~lst)
        ~@result))

(macroexpand-1 (our-dolist [[1 2 3] ] #(println %)))
(macroexpand-1 (our-dolist [[1 2 3] 4] #(println %)))

Section 7.6 A Model of Macros

Graham's our-defmacro, in addition to writing the desired function, also added a property called 'expander and attached it to the created function. I thought Clojure's metadata could serve the same purpose, but I was not able to make it work. Defmacro seems to work, and macroexpand-1 works the same with it.
(defmacro our-defmacro [name params & body]
  `(defn ~name [~@params]
     (do
       ~@body)))

(macroexpand-1 '(our-defmacro test [x] (println x)(+ x 2)))

Section 7.7 Macros as Programs

In this section, Graham shows how lists can be turned into programs by using macros. The expression we would want to use in Clojure though would have the parameters in a map, instead of a list where position matters.

While the named parameters are nicer than the Common Lisp version, at the same time I did cut a couple of corners. I wrote some of the values so that I didn't have to translate them, such as the let binding, which I wrote as one long vector and stated explicitly that z was nil.

;; our desired call
(our-looper {:initial-vals [w 3 x 1 y 2 z nil]
             :body ((println x) (println y))
             :loop-params [x x y y]
             :recursion-expr ((inc x) (inc y))
             :exit-cond (> x 10)
             :exit-code (println z)
             :return-val y})

;; our desired result
(let [w 3 x 1 y 2 z nil]
  (loop [x x y y]
    (if (> x 10)
      (do (println z) y )
       (do
         (println x)
         (println y)
         (recur (inc x) (inc y))))))

;; the macro
(defmacro our-looper [{:keys [initial-vals
                              body
                              loop-params
                              recursion-expr
                              exit-cond
                              exit-code
                              return-val]}]
  `(let [~@initial-vals]
     (loop [~@loop-params]
       (if ~exit-cond
         (do ~exit-code
             ~return-val)
         (do ~@body
             (recur ~@recursion-expr))
         ))))

Section 7.8 Macro Style

I just translated the first implementation of and; as Graham says, it is the more readable.

(defmacro our-and [& args]
  (loop [lst args]
    (cond
     (= (count lst) 0) true
     (= (count lst) 1) (first lst)
     :else (if (first lst) (recur (rest lst)) false))))

Section 7.9 Dependence on Macros

Just as Graham describes for Common Lisp, in Clojure if a function-b depends on function-a, when function-a is updated, function-b will reflect the change. If function-d depends on macro-c, function-d will not be updated when macro-c is updated.

(defn func-a [input]
  (+ input 1))
(defn func-b []
  (func-a 3))
(func-b)
;; 4
(defn func-a [input]
  (+ input 10))
(func-b)
;; 13

(defmacro macro-c [input]
  `(+ ~input 1))
(defn func-d []
  (macro-d 3))
(func-d)
;; 4
(defmacro macro-c [input]
  `(+ ~input 10))
(func-d)
;; 4

Section 7.10 Macros from Functions

The examples from this section are all pretty straight forward.

(defn second-f [x]
  (first (rest x)))

(defmacro second-m [x]
  `(first (rest ~x)))

(defn noisy-second-f [x]
  (println "Someone is taking a cadr")
  (first (rest x)))

(defmacro noisy-second-m [x]
  `(do
     (println "Someone is taking a cadr")
     (first (rest ~x))))

(defn sum-f [& args]
  (apply + args))

(defmacro sum-m [& args]
  `(apply + (list ~@args)))

(defmacro sum2-m [& args]
  `(+ ~@args))

(defn foo [x y z]
  (list x (let [x y]
            (list x z))))

(defmacro foo-m [x y z]
  `(list ~x
         (let [x# ~y]
           (list x# ~z))))

(macroexpand-1
 (foo-m 1 2 3) )

Section 7.11 Symbol Macros

Symbol macros do not exist in core clojure. Konrad Hinsen has a library that adds symbol macros and other useful macro functions.

Tuesday, April 24, 2012

On Lisp in Clojure chapter 7 (7.1 - 7.4)

I am continuing to translate the examples from On Lisp by Paul Graham into Clojure. You can find links to the other posts in this series and the code on the github repository for this project.

Stuart Halloway has also translated this chapter into Clojure on his blog. I definitely recommend reading that.

In Chapter 7 we finally get to macros.

Section 7.1 How Macro's Work

The nil! macro Graham defines sets the variable passed in to nil. Values in Clojure are immutable by default, but there are special constructs for doing mutation. One is the atom.

;; set atom to nil
(def x (atom 0))
(reset! x 5)

(defmacro atomnil! [var]
  (list 'reset! var nil))

(atomnil! x)

Ref's must be mutated within a transaction, which is done with dosync.

;; set ref to nil
(def y (ref 0))
(dosync
 (ref-set y 5))

(defmacro refnil! [var]
  (list 'dosync (list 'ref-set var nil)))

(refnil! y)

Section 7.2 Backquote

Clojure also uses the backquote, usually referred to as the syntax quote which can be unquoted. In Clojure unqouting done with the tilde ~ instead of the comma used in Common Lisp.

(defmacro atomnil! [var]
  `(reset! ~var nil))

(defmacro refnil! [var]
  `(dosync (ref-set ~var nil)))


;; 3 way numerical if
(defmacro nif [expr pos zero neg]
  `(cond
    (< ~expr 0) ~neg
    (> ~expr 0) ~pos
    :else ~zero ))

(nif -1 "pos" "zero" "neg")

Just as the , was replaced by ~ `@ becomes ~@

(def b '(1 2 3))

`(a ~b c)
;; => OnLisp.ch7/a (1 2 3) OnLisp.ch7/c

`(a ~@b c)
;; => OnLisp.ch7/a 1 2 3 OnLisp.ch7/c

Clojure's do is the equivelant of progn in Common Lisp. It executes a series of statements and returns the value of the last expression.

(defmacro our-when [test & body]
  `(if ~test
     (do ~@body)))

(our-when (< 1 2)
          (println "This is a side effect")
          (println "This is another side effect")
          "this is a value")

Section 7.3 Defining Special Macrosk

Clojure does not contain a member function, but we can define one, and also define the memq macro which does the same thing.

(defn member [obj lst]
  (some (partial = obj) lst))

(defmacro memq [obj lst]
  `(some (partial = ~obj) ~lst))

Clojure already has a while loop, which is good, since this implementation isn't very durable.

(defmacro our-while [test & body]
  `(if ~test
    (do
      (swap! ~test not)
      ~@body)))

(our-while (atom true) (println "side effect") "Value")

Section 7.4 Testing Macro Expansion

I like the pretty print macro expansion.

(defmacro mac [expr]
  `(clojure.pprint/pprint (macroexpand-1 '~expr)))

(mac (our-while (atom true) (println "side effect") "Value"))

That seems like a good amount for one post. Will pick up the second half of chapter 7 next time.

Saturday, April 21, 2012

Hello World in ClojureScript

Hello CLJS

Edit October 18, 2013

If you want to get started with ClojureScript I highly recommend that you read Mimmo Cosenza's series of tutorials at https://github.com/magomimmo/modern-cljs . This is the best resource I have found on learning ClojureScript. Please check it out, and don't waste a second reading my old post.

There is probably no reason to keep the original text, but in case there is some value in it I have overlooked, I will leave it unchanged.


I have wanted to learn about ClojureScript, but I haven't known where to start. Like so much in Clojure it turns out to be much simpler than I expected. The instructions for the various projects are each very clear, but I still found it overwhelming at first. Rather than go into detail, I will try to give an overview and link to the related projects.

The appeal of JavaScript, and thus ClojureScript, is that it can be used in so many ways. For example, you can use cljs to do client-side programming in a traditional web application, to do all of the dynamic code in a single page web app, or to do server side scripting in node.js.

Overview

ClojureScript, wherever you use it is compiled to JavaScript. It is the .js file generated by the compiler that you will refer to in your application.

While it is possible to use the ClojureScript compiler directly, the recommended method is to use lein-cljsbuild. If you are creating a new noir web application that you want to use ClojureScript with you can use the cljs-template which will install and configure lein-cljsbuild for you. For anything but a brand new noir project, you will need to set up lein-cljsbuild yourself.

Again, following the instructions on lein-cljsbuild is all you need to do, but I like to see the big picture before I get to the details.

To install cljs-build you add a reference to it with a :pluggins tag on an existing project that you created with leiningen. Configure the plugin by adding :cljsbuild tag, also in the project definition. specifying a path to your ClojureScript source files. If you are writing scripts to use in node.js you will need to specify :target :nodejs in the compiler options. Leiningen will actually install the plugin the first time you try to compile your script files.

Example

I will do a quick walkthrough, to make sure everything is working. I am going to create a very basic script that simply displays an alert when a page is loaded. I will then create a simple html file that will host that script.

My instructions will be very similar to the instructions in the lein-cljsbuild read me, except that I structure my source and destination folders a little differently. Assuming you have Leiningen 1.7 or later installed at the terminal create a new project:

lein new hello-cljs
cd hello-cljs

Edit the project.clj file, adding a :pluggins tag and setting the build options:

(defproject hello-cljs "0.1.0-SNAPSHOT"
  :description "FIXME: write description"
  :url "http://example.com/FIXME"
  :license {:name "Eclipse Public License"
            :url "http://www.eclipse.org/legal/epl-v10.html"}
  :dependencies [[org.clojure/clojure "1.3.0"]]
  :plugins [[lein-cljsbuild "0.1.8"]]
  :cljsbuild {
             :builds [{
                       :source-path "src-cljs"
                       :compiler {
                                  :output-to "web/js/main.js"
                                  :optimzations :whitespace
                                  :pretty-print true}}]})

Create a src-cljs directory, and in it create a file called main.cljs. Your main.cljs should contain the following:

(ns hello-cljs.main)

(js/alert "Hello from ClojureScript.")

From your project's root directory compile the ClojureScript to javascript by typing:

lein cljsbuild once

Compiling will create the destination folders, if they do not already exist.

Go to your web directory, and create a file hello.html:

<html>
 <head>
    <title>Hello CLJS</title>
  </head>
  <body>
    You should have seen an alert if everything is working.
    <script type="text/javascript" src="js/main.js"<>/script>
  </body>
</html>

Not a project that will win any awards, but it is nice to know you are set up correctly.

I wanted to mention one additional thing. In this example we compiled the cljs file to js using the command "lein cljsbuild once". Instead, you can use the command "lein cljsbuild auto" and cljsbuild will monitor your cljs source code directory and recompile any file that changes. Another good option to know is "lein cljsbuild clean" which will delete the compiled js file.

Monday, April 16, 2012

On Lisp in Clojure (chapter 6)

I am continuing to translate the examples from On Lisp by Paul Graham into Clojure.

I have placed the examples from the first 6 chapters on GitHub. The readme links to all of the posts in this series. (Except this one... a fact without a time is incomplete).

Section 6.1 Networks

I have represented the nodes as a map of maps.

(def nodes
  {:people {:question "Is the person a man?" :yes :male :no :female}
   :male {:question "Is he dead?" :yes :deadman :no :liveman }
   :deadman {:question "Was he American?" :yes :us :no :them}
   :us {:question "Is he on a coin?" :yes :coin :no :cidence}
   :coin {:question "Is the coin a penny?" :yes :penny :no :coins}
   :penny {:answer "Lincoln"}})

(defn ask-question [question]
  true)

Since the network is incomplete, I decided not to implement the IO. Making ask-question always return true did require one change from Graham's example. Instead of asking if the person is living, I ask if he is dead, since I only go down the true line.

(defn run-node [name nodes]
  (let [n (name nodes)]
    (if-let [result (get n :answer)]
      result
      (if (ask-question (:question n))
        (recur (:yes n) nodes)
        (recur (:no n) nodes)))))

(run-node :people nodes)

Of course, we want to be able to add nodes programmatically. Instead of optional parameters, in the Clojure implementation we can define a multiple arity function to add both branches and leaves.

(defn add-node
  ([nodes tag answer]
     (conj nodes {tag {:answer answer}}))
  ([nodes tag question yes no]
     (conj nodes {tag {:question question :yes yes :no no}})))

Because nodes is immutable, the following two calls each return a new map that is the original map, plus their one node.

(add-node nodes :liveman "Is he a former president" :texas :california)
(add-node nodes :texas "George W Bush")

The Clojure threading macro, ->, makes it easy to insert the result of one function as a parameter of a second function. The following block creates a new set of nodes with the :liveman tag and passes this to the function that adds the :texas tag. In the end, we get a new map that has both tags added.

(-> 
    (add-node nodes :liveman "Is he a former president" 
         :texas :california)
    (add-node :texas "George W Bush"))

Section 6.2 Compiling Networks

In this section, Graham rewrote the network, adding the function calls to the nodes themselves.

The add-node function becomes

(defn add-node2
  ([nodes tag answer]
     (conj nodes {tag answer}))
  ([nodes tag question yes no]
     (conj nodes {tag (if (ask-question question) 
                           (yes nodes) 
                           (no nodes))})))

I added a couple of nodes, and was surprised by the results:

(def node2
  (-> 
      (add-node2 {} :people "Is the preson a man?" :male :female)
      (add-node2 :male "Is he dead?" :deadman :liveman)))
node2
;; => {:male nil, :people nil}

I decided to start adding from the bottom up:

(def node2
  (-> (add-node2 {} :penny "Lincoln")
      (add-node2 :coin "is the coin a penny?" :penny :coins)
      (add-node2 :us "Is he on a coin" :coin :cindence)))
node2
;; =>  {:us "Lincoln", :coin "Lincoln", :penny "Lincoln"}

I tried rewriting my add-node2 function.

(defn add-node2
  ([nodes tag answer]
     (conj nodes {tag answer}))
  ([nodes tag question yes no]
     (conj nodes
           {tag
            (if ((fn [x] (ask-question x)) question )
              (yes nodes) (no nodes) )})))

I still got the same results.

I tried declaring, but not defining ask-question. When I called add-node2 I got an error that ask-question had not been defined. I tried referring to node2 from another namespace, and still every node evaluated to "Lincoln".

I rewrote the ask-question function to actually ask a question:

(defn prompt [text]
  (do
    (println text)
    (read-line)))

(defn ask-question [question]
  (prompt question))

Now, I get prompted with the question for each node I add. Again, I tried this from a different namespace, and again I was prompted.

I wonder if we have reached the limit of functions. Stay tuned, Chapter 7 begins our journey into the world of macros.

Tuesday, April 10, 2012

On Lisp in Clojure ch 5

I am continuing to translate the examples from On Lisp into Clojure.

Michael Fogus has already translated some of the examples from this chapter into Clojure.

Section 5.1 Common Lisp Evolves

Clojure has "filter" which returns a lazy sequence of items for which a function is true.

(filter even? (range 10))
;; => (0 2 4 6 8)

(filter (complement even?) (range 10))
;; -> (1 3 5 7 9)


(defn joiner [obj]
  (cond
   (sequential? obj) (partial conj obj)
   (number? obj) (partial + obj)))

(defn make-adder [n]
  (partial + n))

Section 5.2 Orthogonality

In Clojure configuration is usually done with vectors and maps, which are immutable, so instead of updating them you would replace them with a new copy.

(assoc {:a 1 :b 2} :b 3)

Changing properties happens a lot more when interoperating with Java. Dave Ray's Seesaw tutorial gives an example of reading and setting properties using Swing.

(def f (frame :title "Getting to know Seesaw"))
…

; The properties of a widget can be queried ...
(config f :title)
;=> "Get to know Seesaw"

; ... and modified
(config! f :title "No RLY, get to know Seesaw!") 
;=> #

The config function is a seesaw function, not a clojure function.

Section 5.3 Memoizing

Memoize is built in to Clojure.

(defn slow [x]
  (do (Thread/sleep 5000) x))
 
(def slow (memoize slow))

(slow 1)

Section 5.4 Composing Functions

Clojure has comp to do compositions:

((comp inc *) 2 2)
;; => 5

Clojure also has a function called 'juxt' which independently applies a series of functions to a single data structure.

  
((juxt inc dec) 2)
;; => [3 1]

Section 5.5 Recursion on Cdrs

This section I found a bit challenging. I thought I was fine with functions returning functions and recursion, but somehow functions returning recursive functions took me a while to get my head around.

First the examples of recursive functions:

(defn our-length [lst ]
  (loop [lst lst count 0]
    (if (seq lst)
      (recur (rest lst) (inc count))
      count )))

(defn our-every [fn lst]
  (loop [lst lst result true]
    (if (seq lst)
      (recur (rest lst)
             (and result (fn (first lst))))
      result)))

And now a function that returns a recursive function:

(defn lrec [trans base]
  (fn [lst]
    (loop [lst lst result base]
      (if (seq lst)
        (recur (rest lst) (trans (first lst) result))
        result))))

((lrec (fn [new acc] (inc acc)) 0) [2 4 6])
((lrec (fn [new acc] (and acc (even? new))) true) [2 4 6 7])

Section 5.6 Recursion on Subtrees

Working with trees in Clojure is done with clojure.zip. I still am not familiar enough with trees to do anything but plagiarize. Instead of that, I will recommend Brian Marick's tutorial on Clojure.zip.

Section 5.7 talks about a behavior of the Common Lisp compiler. I don't know if an analog exists in Clojure. I am just going to skip it.

Monday, April 2, 2012

On Lisp in Clojure ch 4 (4.5 - 4.8)

I am continuing to translate examples from On Lisp by Paul Graham into Clojure. Today I will go over the last few sections of chapter 4.

Section 4.5 Mapping

The map-> function is more concise in Clojure. I also think it is clearer to see that what it is doing is generating a sequence, and mapping a function over that sequence.

In the sample call to map-> I thought it would be fun to describe the functions being passed in 3 different ways, just for variety.

(defn map-> [fn a test-fn succ-fn]
  (map fn (take-while test-fn (iterate succ-fn a))))
 
(map-> inc -2 #(< % 2) (partial + 0.5 ))

Graham presents functions that take in two lists and map a function over the two lists without joining them first. He explains that it doesn't make sense to cons up a list to just pass it to another function and forget it.

Sequences in Clojure are either lazy or persistent. In either case there shouldn't be any penalty for joining the list before passing it into a function.

Section 4.6 I/O

Translating these examples was more about completeness and curiosity. If you are interacting with your program, you will probably use the repl. If you are making something for public consumption, Seesaw is great for doing desktop ui, and Noir is great for doing web interfaces.

(defn read-list []
  (str \( (read-line) \)))

(defn prompt [text]
  (do
    (println text)
    (read-line)))

(defn break-loop [fn quit]
  (let [x (read-string (prompt (str "type " quit " to quit")))] 
    (if (not (= x quit))
      (do
        (fn x)
        (recur fn quit)))))

(break-loop #(println (eval %)) :q)

Section 4.7 Symbols and Strings

Clojure's str function can turn numbers and symbols into strings, and is variadic:

(str Math/PI " pieces of " 'pi)
;;seq can convert strings into sequences of characters
(seq "bomb")
;; => \b \o \m \b

;;strings can be converted to symbols, with or without namespaces
(symbol "foo")
(symbol "some-ns" "foo")

;;Clojure also adds keywords, which you can convert to from strings:
(keyword "foo")
(keyword "some-ns" "foo")

;;If you are not qualifying the keyword with a namespace, you can also create a keyword directly from a symbol
(keyword 'foo)
(keyword "some-ns" (str 'foo))

Section 4.8 Density

This section doesn't have any examples. Graham says that writing utility functions makes your code more concise, which in the long run makes it more readable. Clojure's built in utilities also make code very concise, and also make for a common vocabulary for programmers.

Tuesday, March 27, 2012

Lists, and functions that don't want them

Learning to operate on sequences of data is a continual challenge for me, and probably for other developers coming from an imperative background. I learned a little bit about working with lists yesterday, and I thought I would share it.

Trying to understand "partial" I asked for clarification on IRC. Specifically, I asked whether partial took the next value passed and added it as the rightmost element to the function, as it appeared in the following:

(map (partial + 2) '(1 2 3))
;; => (3 4 5)

When I was told that in fact, partial would take whatever parameters were supplied and add them to the right of the function that was partially declared, I tried removing the map:

((partial + 2) '(1 2 3))
;; => ClassCastException clojure.lang.PersistantList cannot be cast to java.lang.Number

I knew what to change to get it to work:

(apply (partial + 2) '(1 2 3))
;; => 8

I can't say that I understood right away why I needed 'apply' in this example. After some reflection, it seems pretty clear though. I was trying to invoke a function (+ 2 ….) on something. Using '+' with a collection does not work in Clojure.

Adding to a collection is done with 'cons' or 'conj'. I didn't want to put the number 2 into the collection, I wanted to operate on the items in the collection. That is where things like map and apply come in. They reach into the collection and allow you to operate on the members.

map works on each item independently. apply takes all of the items together.

(map (partial + 2) '(1 2 3))
;; => (3 4 5)

(apply (partial + 2) '(1 2 3))
;; => 8

Another function that operates on the members of a list individually is the filter function.

(filter (partial > 10) (range 20))
;; (0 1 2 3 4 5 6 7 8 9)

In the earlier examples the order didn't matter. '+' works the same left to right or right to left. When we use '>' it is important to remember that the values passed in to the function are passed to the right. The results of the filter look backwards if you don't think about how each partial function is applied:

(> 10 0) (> 10 1) .... (> 10 18) (> 10 19)

Do not think of 'partial' as being a place holder, but rather an indicator that more is to come at the end.

Monday, March 26, 2012

On Lisp in Clojure ch 4 (4.1 to 4.3)

I am continuing to translate the examples from On Lisp by Paul Graham into Clojure.

While I was trying to figure out how to implement the prune function in section 4.4, I ran across this post my Michael Fogus: http://blog.fogus.me/2008/10/08/on-lisp-clojure-chapter-4/ Rather than parrot things I don't entirely understand, I will refer the reader to his post. Fogus seemed to stick mostly to section 4.4, so I will cover the other sections here.

Fogus also wrote a post on Chapter 5.

Section 4.1 Birth of a Utility

The examples didn't implement the nicknames function, so I didn't either. As a result, these examples won't actually compile. My all-nicknames implementation assmes that the nicknames function returns a map with the full names as keys, and lists of nicknames as values.

;; this won't compile because nicknames function doesn't exist
;; I am assuming that nicknames will return a list with the name
;; and the matching nicknames
(defn all-nicknames [names]
  ( loop [names names acc {}]
    (if (empty? names)
      {}
      (recur (rest names) (conj (nicknames (first names) acc))))))

;; shorter version
(map nicknames people)

I skipped down to the find2 function in the next set of examples. I did bars instead of bookstores because I can't name bookstores by town. Besides, it allowed a gratuitous Taco Mac reference. This example does work. (This was my first time using if-let, so I had to make sure I was doing it right.)

(defn find2 [fn lst]
  (if (empty? lst)
    nil
    (if-let [val (fn (first lst))]
      {(first lst) val}
      (recur fn (rest lst)))))

(def bars {:atlanta '(taco-mac) :boston '(cheers)  })

(defn return-bars [town]
  (town bars))

(find2 return-bars [:chicago :atlanta)

Section 4.2 Invest in Abstratction

;; compare the length of 2 collections
(> (count [1 2 3]) (count [1 2]))

;; join lists together before mapping over them
(map even? (reduce into '([1 2] [3 4] [5 6])))

Section 4.3 Operations on Lists

The first block of examples illustrate some ways that Clojure is different thatn CLISP. As I understand it, (last '(1 2 3)) would return (3 . nil) in Common Lisp hence the (car (last lst)). In Clojure, (last '(1 2 3)) returns 3. Because of the different structure, the single function doesn't make any sense in Clojure.

The next two functions in the block, append1 and conc1, add an item to a list. conc1 mutates the list and append1 returns a new list. Clojure has a function called conj, which works with each of the Clojure collections appending to the head of a list or tail of a vector. Maps and sets don't keep track of the insert order, but you can add to them as well.

(conj [1 2 3] 4) ;; vector => [1 2 3 4]
(conj '(2 3 4) 1) ;; list => '(1 2 3 4)
(conj #{1 2 3} 4) ;; set => #{1 2 3 4}

Data structures are immutable by default in Clojure, so conj returns a copy of a new collection instead of modifying the collection in place.

The mklst function can be implemented the same way in Clojure if you absolutely want the item in a list, even if the item is already another collection.

(defn mklist [obj]
  (if (list? obj) obj (list obj)))
If you only care that the item is inside of a collection so you can treat it with functions that work on sequences, you can test for sequential?
(defn mklist [obj]
  (if (sequential? obj) obj (list obj)))
Either one can be used with his mapped example:
(map #(mklist (lookup %)) data)

His next example was to use a filter to return 1+ x for each number in a list. In Clojure filter returns the term that returned a true value, not the true value itself. So this function would be written:

(map inc
     (filter
      (fn [x] (instance? Number x))
      ['a 1 2 'b 3 'c 'd  4]) )

If we wanted to add 2 to each number, we could use "partial" as Jacek pointed out in the comments of the last post.

(map (partial + 2)
     (filter (fn [x] (instance? Number x))
          ['a 1 2 'b 3 'c 'd 4]))

The next block of examples all use recursion to work with a list. The longer function walks through 2 lists until the shorter one is exhausted.

(defn longer? [x y]
  (if (or (empty? x) (empty? y))
    (not (empty? x))
    (recur (rest x) (rest y))))

The next example is his filter function. Clojure avoids a lot of recursion by using lazy sequences. Each term is only realized as it is required. So in Clojure, you could get items from an infinite list of odd numbers like this:

(take 5 (filter odd? (iterate inc 1)))
His group function is also implemented in Clojure in a lazy way.
(partition 2 [1 2 3 4 5])
;; ((1 2) (3 4))
(partition-all 2 [1 2 3 4 5])
;; ((1 2) (3 4) (5))
(take 5 (partition 2 (iterate inc 1)))
;; ((1 2) (3 4) (5 6) (7 8) (9 10))

Section 4.4 Search

While researching the examples for this section I discovered that Michael Fogus had already translated these examples in his blog. He covered the section much better than I can. In my next post, I will pick things up again in section 4.5.

Monday, March 19, 2012

On Lisp in Clojure ch 3

I am continuing to translate the examples from On Lisp by Paul Graham into Clojure. Today I am looking at chapter 3.

Section 3.1 Functional Design

Graham shows an example of a bad-reverse function, which modifies the list it was passed and then shows a good-reverse which returns a new list. I am not going to translate the bad example, because it is even uglier in Clojure, where you have to go out of your way to mutate things.

(defn good-reverse [lst]
  (loop [lst lst acc ()]
    (if (= () lst)
      acc
      (recur (rest lst) (cons (first lst) acc )))))

(good-reverse [1 2 3 4])

The next bunch of examples talk about different Lisp functions that alter the values of their parameters. None of the examples really make sense in Clojure. We will talk more about that in section 3.3.

The truncate example was interesting. I am not sure why you would have a function that returns multiple scalars in a list based language. Why not return a list? Clojure does not have a truncate function, but you can use quot and rem to get the same effect.

(defn split-decimal [n]
  {:quotient (quot n 1)  :remainder (rem n 1) :quotent-int (int n)})

(split-decimal 26.235)
(split-decimal 26.235M)

The split-decimal function returns a map that contains 2 floats and an int when called with a float, and 2 decimals and an int when called with a decimal.

Section 3.2 Imperative Outside-In

To square a number we can either use Java's Math class or Clojure's expt function. Java's Math.pow returns a double:

(defn fun [x]
  (list 'a (Math/pow (first x) 2)))

The exponent function in Clojure is stored in a library called math.numeric-tower. It will return an int when passed two ints, and return a double when one of the parameters is a double.

To get math.numeric tower, you need to add a dependency to the project.clj file. After the add, the dependency section in my project.clj looks like:

:dependencies [[org.clojure/clojure "1.3.0"]
               [org.clojure/math.numeric-tower "0.0.1"]]

You import this dependency by typing lein deps at the command line. (Assuming you are using Leiningen, and why wouldn't you?)

The functional version of his example is:

(use '[clojure.math.numeric-tower])

(defn fun [x]
  (list 'a (expt (first x) 2)))

I thought the imperative version of the function was extra awkward, probably because in CLISP let does not bind sequentially. In Clojure where let does bind sequentially, and mutating a variable takes extra work, it makes sense to assign your variables when you declare them. That is how I would do it in C# too, so I think it is a reasonable imperative idiom.

(defn imp [x]
  (let [y (first x) sqr (expt y 2)]
    (list 'a sqr)))

Section 3.3 Functional Interfaces

This section makes Clojure look like a better Lisp than Lisp. The first example shows a call to a function nconc, which joins lists together and then puts the result into the first list. His function manages to work in a good functional style because he makes a copy of the list he is passed in, and passes the copy to the nconc function. By default Clojure doesn't mutate data in place it returns a new copy.

(defn qualify [expr]
  (cons 'maybe expr))

(qualify '(this is true))

Using cons puts the 'maybe at the front of either a list or a vector. If you rewrite the function using into, the 'maybe will get added to the front of a list or the end of a vector.

(defn qualify [expr]
    (into expr '(maybe)))

(qualify ['this 'is 'true'])

The next example is of calling a function that increments a variable and returns the new value. Again, Clojure does by default what Graham is advocating. The difference is, in Clojure Graham's right way is also the easy way.

;; x is immutable
(let [x 0]
  (defn total [y]
    (+ x y)))

;; x is mutable
(let [x (atom 0)]
  (defn total [y]
    (swap! x #(+ % y))))

Clojure makes mutable state available when you need it, but mutability always takes more work than immutability. What's more, if you have something that you want to be mutable, you have to declare it as a mutable type (here we use an atom). When you are using values instead of variables, you have a guarantee that no other function can change that. You only have to worry about mutation in things that are mutable, which are either Clojure's mutable structures or mutable Java objects when doing interop.

Rather than go through the rest of the examples in this section, I will just take comfort that Clojure encourages me to do things in a way Graham is advocating.

Section 3.4 doesn't have any examples. It does give a good explanation of some benefits of functional programming though.

And that concludes chapter 3.

Monday, March 12, 2012

Looking Forward to Clojure West

This may sound like an advertisement, but hey, I am really looking forward to the conference.

Clojure West starts this Friday, March 16. Two days, 4 keynotes, 3 tracks with numerous sessions. There is going to be an Overtone jam session (with Heroku buying the beer), and we will get to see how they do Swarm Coding in Seattle.

I don't think I will be able to finish watching all of the videos from the last conference before this one starts. Two I recently watched that I really enjoyed were Kevin Lynagh discussing the advantages of ClojureScript over JavaScript from the 2011 Conj, and Chris Houser talking about Finger Trees (which look really useful despite the strange name) from the 2010 Conj. Both Lynagh and Houser are giving presentations at this conference as well.

There are still spaces available. It is also possible to get tickets for just Friday or just Saturday if that appeals to you. See you there?

Monday, March 5, 2012

On Lisp in Clojure ch 2 (2.7 - 2.10)

This is the fourth post translating the examples from chapter 2 On Lisp by Paul Graham into Clojure.

Section 2.7 Local Functions

;; apply function to all items in list
(map (fn [x] (+ 2 x))
     '(2 5 7 3))
;; or
(map #(+ 2 %)
     '(2 5 7 3))

The copy tree function didn't seem to do anything, the data looks the same to me after as it did before. But I think the point is that you can use map with a named function.

(map inc '(1 2 3))

The next example is a function that applies a function to each element of a list using a closure

(defn list+ [lst n]
  (map #(+ n %) lst))
(list+ '(1 2 3) 3)

The next set of eamples pertain to CLISP's labels function, which does not exist in Clojure. In Clojure let is evaluated sequentially so things that Graham says won't work in CLISP work in Clojure such as:

(let [my-inc (fn [x] (+ x 1))] (my-inc 3))
(let [x 10 y x] y)

The last example in this section is of mapping a recursive function to a list. I did my best to do a translation of this function into Clojure, but it doesn't actually work. It blows the stack. I have included it anyway, because it shows naming a function with the (fn name [params] form. The only recursion you want to use in Clojure is tail recursion, which is the subject of the next section. Generally, in Clojure though, you use sequences instead of recursion, but that discussion doesn't really fit here.

(defn count-instances [obj lists]
  (map (fn instances-in [lst]
    (if (seq? lst)
      (+ (if (= (first lst) obj) 1 0)
         (instances-in (rest lst))) 0)) lists))

Section 2.8 Tail-Recursion

Tail recursion in Clojure uses the recur form. The java virtual machine does not support tail call optimization. The recur form tells the Clojure compiler to compile the code to a loop to compensate.

I skipped the non-tail call recursive example of the our-length function.

(defn our-find-if [pred lst]
  (if (pred (first lst))
    (first lst) (recur pred (rest lst))))
(our-find-if even? [1 2 3 4])
The tail call version of our-length.
(defn our-length [lst]
  (loop [lst lst acc 0]
    (if (= () lst)
      acc
      (recur (rest lst) (+ acc 1) ))))
(our-length '(1 2 3 4))

This section ends with a discussion of optimization of Common Lisp. In Clojure you can get better performance using type hints. This tells the compiler which java type to use for a variable. Here is the Clojure optimized triangle function.

(defn triangle [^long n]
  (loop [c 0 n n]
    (if (zero? n)
    c
    (recur (+ n c) (- n 1)))))
(triangle 1000000)

The type hint gives an extra boost in this case. Normally the type hint makes reflection unnecessary. Here, we are specifying to use a java primitve (long) instead of a java object to hold the number. On my system, without the type hint the (triangle 1000000) call took 521 milliseconds. When I added the type hint, it went down to 11 milliseconds!

Section 2.9 covers compilation. Graham distinguishes between functions that are complied verses functions that are interpreted. In Clojure all functions are compiled.

Clojure does have a compile function, that was added in version 1.3. The documentation says that it is for compiling libraries, so it is not analgous to the compilation discussed in this section of On Lisp.

Section 2.10 does not contain any examples.

That's all for Chapter 2.

Thursday, March 1, 2012

On Lisp in Clojure ch 2 (2.5 - 2.6)

This is my third post translating the examples from On Lisp by Paul Graham into Clojure.

Section 2.5 Scope

This section shows an example and describes how it would be evaluated with dynamic scope and lexical scope. Here is the example with Clojure syntax:

(let [y 7]
  (defn scope-test [x]
    (list x y)))

(let [y 5]
  (scope-test 3))

Like CLISP, Clojure uses lexical scope in this example, and like CLISP, there are ways to use dynamic scope. Amit Rathore covers scope in detail in Clojure in Action, but Graham doesn't cover in this part of his book, so I won't either.

Section 2.6 Closures

In the first example, the inner anonymous function gets the value of n from its enclosing function.

(defn list+ [lst n]
  (map (fn [x] (+ x n))
       lst))

(list+ '(1 2 3) 10)

Clojure's data structures are immutable by default, but the next example doesn't work without mutable state, so this version uses a Clojure atom.

;; lexically scoped counter
(let [counter (atom 0)]
  (defn new-id [] (swap! counter + 1))
  (defn reset-id [] (reset! counter 0 )))

(new-id)
(reset-id)

The next example defines a function that returns a function that adds a predetermined number.

(defn make-adder [n]
  (fn [x] (+ x n)))

(def add2 (make-adder 2))
(def add10 (make-adder 10))
(add2 5)
(add10 3)

The next example again creates an adder function, but an optional boolean parameter lets the caller change the amount that gets added with each call. Again we will use a Clojure atom for the mutable variable.

(defn make-adderb [n]
  (let [amt (atom n)]
    (fn [x & change ]
      (if change  (reset! amt x ))
      (+ x @amt))))

(def addx (make-adderb 1))

(addx 3)
(addx 100 true)
(addx 3)

The next example was out of order in the book. In the proper order, we create a make-dbms function that takes a collection of key value pairs and returns a list of functions that operate on that collection. In Clojure the logical data type to use is a map, rather than a list of lists. The coolness of this example, using a list of functions that operate on a collection provided by a closure work just fine with immutable state.

(defn make-dbms [db]
  (list
   (fn [key]
     (db key))
   (fn [key val]
     (assoc db key val))
   (fn [key]
     (dissoc db key))))

(def cities (make-dbms {'boston 'us, 'paris 'france}) )

cities is a list of functions that operate on the map of key value pairs. The comma in the collection is optional, I just think it makes the grouping more clear. Commas are whitespace in Clojure.

Here is how we call the functions:

((first cities) 'boston)
((second cities) 'london 'england)
((last cities) 'boston)

Even for a contrived example, we can't really get away with an immutable database. So here is the mutable version, again using atoms.

(defn make-mutable-dbms [db]
  (let [mdb (atom db)]
    (list
     (fn [key]
       (@mdb key))
     (fn [key val]
       (swap! mdb assoc key val))
     (fn [key]
       (swap! mdb dissoc key)))))

(def citiesx (make-mutable-dbms {'boston 'us, 'paris 'france}) )

((first citiesx) 'boston)
((second citiesx) 'london 'england)
((last citiesx) 'boston)

In a clear victory for hammock driven development, I realized that a map of functions made a lot more sense than a list of functions. This way, instead of calling first, second and last, we can call the functions by name, like so:

(defn make-dbms-map [db]
     (let [mdb (atom db)]
       {:select (fn [key] (@mdb key))
        :insert (fn [key val]
                  (swap! mdb assoc key val))
        :delete (fn [key]
                  (swap! mdb dissoc key))}))

(def citiesm (make-dbms-map {'boston 'us 'paris 'france}))
((:select citiesm) 'boston)
((:insert citiesm) 'london 'england)
((:delete citiesm) 'boston)

viva la clojure

Next time we will finish Chapter 2, covering local functions and tail recursion.

Tuesday, February 28, 2012

On Lisp in Clojure ch 2 (2.4) Polymorphism

This is my second post translating the examples from On Lisp by Paul Graham into Clojure.

Section 2.4 is titled Functions as Properties. What Graham is describing in his example is polymorphism, and there are a couple of ways to do this in Clojure.

First, here is the Clojure version of the method using a conditional statement.

(defn behave [animal]
  (cond
   (= animal 'dog) (do '(wag-tail) '(bark))
   (= animal 'rat) (do '(scurry) '(squeek))
   (= animal 'cat) (do '(rub-legs) '(scratch-carpet))))

My version has a lot of quotes where the original does not, such as '(dog) and '(wag-tail) because I wanted my code to compile, without actually having to create a wag-tail function. Any new animals we create will require editing our behave function.

Rather than go into the details of Graham's alternative method in the book, I will just jump to two ways to do the same thing in Clojure.

Protocols

The first is with protocols. A protocol is a list of functions that can be applied to different data-types. Each function must take at least 1 parameter. It is this required parameter that determines what actually gets called at run time. Protocols are applied to data types that are defined with either deftype or defrecord. For the purposes of protocols, the two are interchangeable, as in my example:

;; define the protocol
(defprotocol animal
  (behave [this] ))

;; define a dog
(defrecord dog [breed]  )

;; add the animal protocol to dog type
(extend dog
  animal
  {:behave (fn [src] (do '(wag-tail) '(bark)))})

;; create a dog
(def my-dog (dog. "collie"))

;; see what it does
(behave my-dog)

;; define a rat
(deftype rat [color])

;; add the animal protocol to the rat type
(extend rat
  animal
  {:behave (fn [src] (do '(scurry) '(squeek)))})

;; create a rat
(def brown-rat (rat. "brown") )

;; see what it does
(behave brown-rat)

Protocols allow you to add polymorphic behaviors to any data type. To get an idea of how powerful they are try typing this in:

(extend String
  animal
  {:behave (fn [src] (do '(what)))})

(behave "huh")

Then consider that java.lang.String is declared as final.

Multimethods

While protocols are similar to overriding functions, multimethods are like overloading. Protocols broadened overriding to make polymorphism work independent of class hierarchies. Multimethods allow overloading based not just on parameter type, but even parameter values.

Here's the multimethod version of the book's example.

;; define the multimethod type
(defmulti behave-multi identity)

;; define implementations for our animals
(defmethod behave-multi 'dog [x]
  (do '(wag-tail) '(bark)))
(defmethod behave-multi 'rat [x]
  do '(scurry) '(squeek))

;; try them out
(behave-multi 'dog)
(behave-multi 'rat)

The following example is pretty dumb, but it will show you that you a way to choose which function to call based on variable values, instead of just variable types in traditional overloading.

(defmulti two-behaviors (fn [num]
                          (if (odd? num)
                            :odd
                            :even)))

(defmethod two-behaviors :odd [num]
  (str num " is odd"))

(defmethod two-behaviors :even [num]
  (str num " is even"))

(two-behaviors 3)
(two-behaviors 4)

This was just a glimpse into protocols and multimethods in Clojure. The Clojure books I have seen devote a chapter to each, and I suspect they still leave a lot unsaid.

Monday, February 27, 2012

On Lisp in Clojure ch 2 (2.1 - 2.3)

This is the first post translating the examples in On Lisp into Clojure. The book is available to read for free online, so please read the book, and check here if you are not sure how it applies to Clojure.

In the book, chapter 1 described the extensibility and flexibility of Lisp. In short, it lays out the reason I am going through the book. The few code samples in this chapter didn't seem to benefit from translation though.

Chapter 2 is about Functions. Section 2.1 discusses functions as a data type. It doesn't contain any examples.

Section 2.2 Defining Functions

;; double function
(defn double [x] (* x 2))

;; invoking double
(double 1)

;; referring to the function as a variable
#'double
(= #'double (first (list #'double)))

;; lambdas are defined two ways in Clojure
(fn [x] (* x 2))
#(* % 2)

;; invoking an anonymous function
((fn [x] (* x 2)) 3)
(#(* % 2) 3)

Next, the book assigns a variable double, and shows that the function and the variable can exist side by side with the same name. This works in common lisp, because it has a separate namespace for functions and variables it does not work in Clojure. CLISP is said to be a LISP-2 (Two namespaces) While Clojure (and scheme) are LISP-1s.

;; we can assign assign a function to a variable
(def x #'double)
(x 2)

Section 2.3 Functional Arguments

;; four expressions with the same effect
(+ 1 2)
(apply + '(1 2))
(apply + 1 '(2))
(apply + 1 2)

;; funcall doesn't exist in Clojure

;; map applies a function to each argument in a list
(map #(+ % 10) '(1 2 3))
(map + '(1 2 3) '(10 100 1000))

;; sort is ascending by default
(sort '(1 4 2 5 6 7 3))
;; to specify sort order, pass the function then the list
(sort > '(1 4 2 5 6 7 3))

;; instead of remove-if, in Clojure use filter, true values are returned
(filter odd? '( 1 2 3 4 5 6 7))
;; pred can also be an anonymous function
(filter #(= 0 (rem % 3)) '(1 2 3 4 5 6 7 8 9))

;; our-remove-if was implemented with recursion in the book.
(defn our-remove-if [pred lst]
  (if (empty? lst)
    nil
    (if (pred (first lst))
      (our-remove-if pred (rest lst))
      (cons (first lst) (our-remove-if pred (rest lst))))))

(our-remove-if even? '(1 2 3 4 5))

;; The actual filter function is implemented with a lazy sequence
;; You can see the implementation of core functions with (source ...)
(source filter)

I am going to stop here, because section 2.4 is a big enough topic that it should have its own space.

Reading On Lisp to learn Clojure

When I read Beating the Averages by Paul Graham, I knew I needed to look into Lisp.

One of the first things I learned was that "Learning Lisp" really meant learning a Lisp. Lisps are a family of languages with some common attributes. The most significant attribute is that Lisp code is written in a Lisp data structure. Since code manipulates data, and code is data, code can manipulate code. This manipulation is done with Lisp macros.

Because there are several languages that are Lisps, I had to pick one. I opted for Clojure, initially because it could compile down to .NET IL or Java byte code or Javascript. Soon I found out how well thought out its data structures and support for concurrency is.

I am confident that Clojure is the right Lisp for me, but that still begs the question, is Lisp right for me. Are Lisp macros really that powerful? Chas Emeric in Clojure Programming describes how Lisp macros are different from other languages' meta-programming support. They are code, not strings. They are applied at compile time, not at run time. They are using the same code that the programs use, not special api calls. But does all this matter?

It was Graham's essay that prompted the question, and I am hoping that one of Graham's books can answer it. On Lisp is available to read free online. According to the preface, the first 6 chapters deal with functions and the remaining 19 deal primarily with macros.

On Lisp should help me learn to think in macros. It is written in Common Lisp, which is different than Clojure. Hopefully translating it will help me to think in Lisp in Clojure.

I am not going to copy the whole book. I plan to post Clojure versions of the examples, with some explanation when it seems appropriate. If you want to play along, start reading Graham's book, and check back here for my Clojure interpretations of it.

Saturday, February 25, 2012

Different Platform/Different World

Between .NET and the JVM is a much wider gulf than I had imagined. Switching from C# to Clojure has meant 3 changes: imperative to functional, non-lisp to lisp and .net to jvm.

The switch from imperative to functional is a recurring theme on this blog. The reasons for switching to a Lisp will be the subject of another post (maybe posts). Switching platforms was incidental and that made it all the harder.

C# and Java are similar, but the programmers think differently. If you find yourself switching from one platform to the other, it may go more smoothly if you are aware of the differences.

.NET is punctuated equilibrium. Java is incremental evolution.

On the .NET platform, from time to time Microsoft releases a new version with new features and this becomes the new standard. Cases where Microsoft says that the new technology is an alternative, not a replacement, only mean that the transition will go a little slower.

To be a .NET developer is to be a Visual Studio developer. It is the IDE. It is also the build tool and dependency manager. Changes to the IDE are changes to the platform and changes to the platform have to be supported by the IDE to be adopted.

In the Java world, new practices come more from ideas, libraries and tools coming from the community than from the company controlling the language (first Sun, now Oracle). When a library becomes standard, it is because the community has found it useful. There are several different IDEs, and there are developers who don't use IDEs at all.

Living in the .NET world is long periods of comfort interrupted by periodic shocks. Visual Studio is a great tool, there is a standard way to do things and there is great support for the standard. Each .NET release is an epochal change from the prior version. The new versions tend to be great, but they are sudden, and often huge, changes.

Based on what I can see on the outside, it looks like it is the responsibility of each organization that uses the JVM to determine the right way to do things. It means working hard to keep up with many different projects each taking its own approach to solving an individual program.

If you work on the JVM, you have to spend more time thinking about your tools, but if you work hard to keep up do you avoid abrupt changes. Not having lived through it, I can't say, but I sure hope so!

Wednesday, February 15, 2012

Project Euler and Refactoring

I started doing the problems on Project Euler the other day. For anyone that doesn't know, Project Euler is a website that has a collection of math problems for you to solve. You can solve the problem any way you want. The site keeps track of which problems you have submitted correct answers to.

Just finding the right answer is a good programming challenge, but refactoring makes for much deeper learning.

Another benefit from doing the problems is that you are building samples of your work that you can show to prospective employers. If you are going to show the world your code, you want it to be clean.

Here is an example of my process solving one of the problems in Clojure. I can't show what I have learned without displaying my ignorance, but I am less ignorant now because of this process.

Every line of code you see here represents at least 5 lines of experimentation preceding it.

Problem 3 asks, "What is the largest prime factor of the number 600851475143 ?"

Solution 1

Find all of the divisors of n, filter the ones that are prime and then take the largest. To find all of the divisors, iterate through all of the numbers from 1 to n, and test remainder of n divided by i.

Works just fine with 42. Doesn't show any signs of returning with 600851475143 . Restart the REPL.

  • Learned a bit more about 'for' like the difference between :while and :when.

Solution 2

Create a function that finds a single factor, called afactor. In Clojure you don't use loops with breaks, you use sequences and take the items you want. Lazy sequences don't calculate numbers until you ask for them, so you can create an expression which calculates all of the divisors, but only actually calculate one or two.

(defn afactor [base]
  (nth (for [x (range 1 (+ 1 base))
             :when (= 0 (rem base x))] x ) 1))

  • Learned how to use 'for' in a lazy way.

Now to create a function that returns a pair of factors.

(defn factor [base]
  (let [first (afactor base) ]
    (list first (/ base first))))

  • Got more confidence with 'let' binding.

The next step is a test whether a number is prime. A prime number has 2 divisors, but counting the number of divisors of our number is going to leave us restarting the REPL again, which of course is just a menu item in Clooj, but it is painful to admit that I was dumb enough to think that would work, so we will skip that step. Since a prime number is only divisible by 1 and itself, its 2nd largest factor will be itself.

(defn prime? [base]
  (= base (afactor base) ))

  • I assumed (= base (afactor base)) would allow me to return a boolean, glad to see that it actually does.

The first call to factor with our number yields a result large enough that I don't care to retype it. Let's set up a manual recursion of 1 level.

(defn prob3 [base]
  (map factor 
       (filter #(complement prime?
                (factor base)))))

  • Playing around with this function and others like it really got me confident with the #(%) syntax of anonymous functions. Not long ago they were a mystery, but with repetition they are comfortable.
  • Playing with the ugly (map factor (filter ... construction was good practice with maps and lists even if the resulting code is terrible.

It is not hard to see a way to the right answer from this. Either you take the output of prob3 and call prob3 again, typing in the first result, or you could nest the map factor filter inside of another map factor filter. This isn't anything you are going to show off to your friends.

Solution 3

Solving a problem earlier on 4clojure I found out that Clojure has a function called tree-seq. We always drew trees when we were factoring numbers in school, so that will probably yield a more satisfying result. Tree-seq takes 3 parameters, branch? children and root. branch? is a function that tests whether a node has children, children is a function that returns the children for a node and root is the initial value.

(defn factor-tree [base]
  (tree-seq (complement prime?) factor base))

  • I got to learn how to use tree-seq. Also, prime? was returning true when a node didn't have children, exactly opposite the desired result. After (not prime?) failed, I understand when to use not and when to use complement.

factor-tree is returning a list of all of the factors. That is easy enough to handle. Getting all of the prime factors we may want to do on another problem, so lets give it its own function.

(defn prime-factors [base] 
    (filter #(prime? %)  (factor-tree base)  ))

For this problem, we just want the largest prime factor.

(defn problem3 []
  (apply max (prime-factors 600851475143)))       

  • I was surprised that I had to type (apply max(...)) instead of just (max (..)). In the imperative world so often you are calling methods on parameters, so it is not hard to think of LISP syntax differently. Every language I have ever used though has had a function called max that operates on a list of data, which is why it is hard for my brain to see that max(list) isn't correct.

Solution 4

Using the tree-seq makes for a much nicer solution, and I was tempted to stop there. One thing still bothered me though. In one video I saw, Stuart Halloway said that with lazy evaluation, there seldom was a reason to return just one of anything. It is much more flexible to return a sequence and let the caller decide which elements they need.

(defn afactor [base]
  (nth (for [x (range 1 (+ 1 base))
             :when (= 0 (rem base x))] x ) 1))

Needs to be rewritten.

(defn lazy-factor [base]
  (for [x (range 1 (+ base 1))
     :when (= 0 (rem base x))]
     x ))
 

  • The idea of returning a lazy sequence instead of a single value is a different philosophy that I have used in the past.

As you can see, the change was very minor. In fact, it is easier to do it the right way than the wrong way. If I hadn't rewritten it, I never would have found that out!

Because I am now returning a lazy sequence instead of a single element, I do have to modify the callers to choose the element they want.

(defn prime? [base]
  (= base (nth (lazy-factor base) 1)))

(defn factor [base]
  (let [first (nth (lazy-factor base) 1) ]
    (list first (/ base first))))

Solution 5

I thought I was done, but moving when I moved on to other problems, I kept finding myself typing things like (range 1 (+ 1 base)), as I did in the lazy-factor function. Range is built to give you a c style loop, so (range 5) gives you (0 1 2 3 4). Usually this is fine, but for the Project Euler problems, I constantly find myself wanting a basic style loop, (1 2 3 4 5) instead. This was enough motivation for me to attempt my first macro.

(defmacro rangeb [last]
  (list 'range 1 (list '+ 1 last)))

With this change, lazy-factor becomes:

(defn lazy-factor [base]
  (for [x (rangeb base)
     :when (= 0 (rem base x))] 
     x ))

Conclusion

I expect that in the not too distant future I will be able to look back at this post and cringe. I am sure that I will find other situations where I find a simpler way to do things and will be tempted to refactor again.

I find myself using 'for' quite a bit, though only in the factor function (afactor and then its replacement lazy-factor) here. for feels imperative, and I wonder if I am overusing it.

My rangeb macro is overly specific. Right now you can only pass an ending number; it always starts at one and increments by one. When the spirit moves me, or when a situation demands it, I will update it. In the meantime I will pretend that YAGNI applies here.

One other thing I think my subconscious is learning is how easy it is to write and test things in Clojure. Next time I use C# I am sure I am going to miss the REPL. Even now, I can ponder having to write methods to call and output my code, compiling every change. /shudder