Agents of Swing

The title of this post would make a good name for a band.

Anyway, today I’m going to talk about Swing and concurrency and Clojure.

The Swing framework is not thread-safe. That may sound strange at first, but there’s actually some sound technical reasoning behind it.

Basically, the Swing designers realized that, in order to have a multi-threaded GUI, you need locks everywhere, which typically means you have bugs everywhere.

That’s not to say a Swing application can’t be multi-threaded. Swing merely requires that the GUI be single-threaded. In Swing, all GUI-related code must run on a special thread called the event dispatch thread, which is automatically created by the Swing framework.

By design, event listeners such as ActionListener.actionPerformed always run on the event dispatch thread. To run arbitrary code on the event dispatch thread, you can use the SwingUtilities.invokeLater method.

As was pointed out in a comment on my last post, this is how all of my example apps should be started. The invokeLater method takes a Runnable argument. In Clojure, this is easy, because all Clojure functions are Runnable. So, for example, the temp-app program should be started like this:

(SwingUtilities/invokeLater temp-app)

As a consequence of running all GUI code on a single thread, any GUI code that blocks can “freeze” the entire application. Event listeners, therefore, must execute quickly and delegate long operations like I/O to other threads.

Java 6 provides the SwingWorker class to manage long-running background tasks. Unfortunately, the implementation of SwingWorker is heavily dependent on protected methods and concrete inheritance, features that are awkward to use in Clojure.

But wait, wasn’t Clojure designed for concurrency? Yes it was, and we can replace SwingWorker with Clojure’s more-powerful tools.

In this post, I will recreate the Flipper application from the Swing tutorials.

* * *

The point of Flipper is to test the “fairness” of Java’s random number generator. It uses java.util.Random to generate random booleans, simulating a series of coin flips. The number of “heads” (boolean true) should converge to half of the total number of flips.

The Java version of Flipper (source here) does the coin flips in a SwingWorker thread, which sends intermediate results to a GUI.

Our version will use Clojure Agents, a much more flexible and powerful alternative.

Lets dig into some code. First, we need a function to create a “Flipper” agent:

(defn new-flipper []
  (agent {:total 0, :heads 0,
          :running false,
          :random (java.util.Random.)}))

This sets up the initial state of the agent, with its own random number generator, two counters, and a boolean flag to designate whether or not the flipper is running.

The flipper agent will have three actions. An agent action is just a function taking one argument, which is the current state of the agent. Whatever the function returns becomes the new state of the agent.

Additionally, in the body of the action, the special Var *agent* is bound to the agent itself. The action function can send other actions to *agent*; those actions will not run until after the current action completes.

Our flipper’s first action is calculate:

(defn calculate [state]
  (if (:running state)
    (do (send *agent* calculate)
        (assoc state
          :total (inc (:total state))
          :heads (if (.nextBoolean (:random state))
                   (inc (:heads state))
                   (:heads state))))
    state))

If the flipper is currently “running,” calculate will call the random number generator and update the counters. It will also send itself to the agent again, creating a loop.

If the flipper is not “running,” calculate does nothing, but it must still return the original state.

The remaining two actions control the “running” state of the agent:

(defn start [state]
  (send *agent* calculate)
  (assoc state :running true))

(defn stop [state]
  (assoc state :running false))

These actions just change the value of :running in the agent’s state. The start action also sends the calculate action to kickstart the calculation loop.

To watch the agent in action, try this at the REPL:

(def flipper (new-flipper))
(send flipper start)

The flipper is now running in the background. At any time, you can retrieve the current state of the flipper with (deref flipper), or simply @flipper. Try it a few times and see how the counters change, as in this sample REPL session:

user> @flipper
{:total 365067, :heads 182253, :running true, ...
user> @flipper
{:total 679283, :heads 338549, :running true, ...
user> @flipper
{:total 1030204, :heads 513767, :running true, ...

To stop the calculation, type

(send flipper stop)

Subsequent calls to @flipper will all show the same value. You can restart the calculation by typing (send flipper start) again.

We need one more function to make our flipper complete. We want to compute the “unfairness” of the random number generator, or how far it is from 0.5. This is easy:

(defn error [state]
  (if (zero? (:total state)) 0.0
      (- (/ (double (:heads state))
            (:total state))
         0.5)))

The if expression is just there to avoid divide-by-zero errors in the initial case.

Note that, although I used the same argument name, state, as in the actions, the error function is not meant to be called as an action with send. Instead, we will call it on the current state of the agent like this:

(error @flipper)

* * *

The nice thing about this flipper is that, unlike the Java version, it is completely decoupled from the GUI. We can design and test it at the REPL before writing any GUI code at all.

(The Java version could have been decoupled. But because Swing requires you to create so many classes anyway, the temptation is always there to combine GUI code with “process” code.)

So let’s get this GUI going. Unlike the Java example, which used callbacks from the flipper to update the GUI, our GUI will update at a fixed rate of 10 times per second. To do this we will use a javax.swing.Timer, which fires an event every n milliseconds.

First, some imports and a helper function to create the text fields with common attributes:

(import '(javax.swing JPanel JFrame JButton JTextField
                      JLabel Timer SwingUtilities))

(defn text-field [value]
  (doto (JTextField. value 15)
    (.setEnabled false)
    (.setHorizontalAlignment JTextField/RIGHT)))

Next, we will reuse the on-action macro from an earlier post, except I’ve renamed it with-action because my editor’s automatic indentation looks better that way.

(defmacro with-action [component event & body]
  `(. ~component addActionListener
      (proxy [java.awt.event.ActionListener] []
        (actionPerformed [~event] ~@body))))

And now we’re ready for the app itself:

(defn flipper-app []
  ;; Construct components:
  (let [flipper (new-flipper)
        b-start (JButton. "Start")
        b-stop (doto (JButton. "Stop")
                 (.setEnabled false))
        total (text-field "0")
        heads (text-field "0")
        t-error (text-field "0.0")
        timer (Timer. 100 nil)]

    ;; Setup actions:
    (with-action timer e
      (let [state @flipper]
        (.setText total (str (:total state)))
        (.setText heads (str (:heads state)))
        (.setText t-error (format "%.10g" (error state)))))
    (with-action b-start e
      (send flipper start)
      (.setEnabled b-stop true)
      (.setEnabled b-start false)
      (.start timer))
    (with-action b-stop e
      (send flipper stop)
      (.setEnabled b-stop false)
      (.setEnabled b-start true)
      (.stop timer))

    ;; Create window and layout:
    (doto (JFrame. "Flipper")
      (.setContentPane
       (doto (JPanel.)
         (.add (JLabel. "Total:"))
         (.add total)
         (.add (JLabel. "Heads:"))
         (.add heads)
         (.add (JLabel. "Error:"))
         (.add t-error)
         (.add b-start)
         (.add b-stop)))
      (.pack)
      (.setVisible true))))

The GUI has three text fields showing the total number of flips, the number of “heads,” and the error rate. The “Start” button starts the flipper; the “Stop” button suspends it. You can start and stop as many times as you like without losing the results of the calculation (another improvement over the Java version, which restarts at zero each time).

The important code is in the with-action bodies. (Don’t confuse Swing ActionListeners with Agent actions.) Remember, event listeners must execute quickly, so all they do is update the visible parts of the GUI.

The “Start” button kicks off the flipper and activates the Timer. The Timer fires every 100 milliseconds, updating the text fields from the current state of the flipper. The “Stop” button suspends both the Timer and the flipper.

Run the application like this:

(SwingUtilities/invokeLater flipper-app)

We didn’t do any fancy layout because it wasn’t necessary for the example. But if you want something prettier, here’s another version using the GridBagLayout macros from my last post:

(import '(java.awt GridBagLayout Insets))

(defmacro set-grid! [constraints field value]
  `(set! (. ~constraints ~(symbol (name field)))
         ~(if (keyword? value)
            `(. java.awt.GridBagConstraints
                ~(symbol (name value)))
            value)))

(defmacro grid-bag-layout [container & body]
  (let [c (gensym "c")
        cntr (gensym "cntr")]
    `(let [~c (new java.awt.GridBagConstraints)
           ~cntr ~container]
       ~@(loop [result '() body body]
           (if (empty? body)
             (reverse result)
             (let [expr (first body)]
               (if (keyword? expr)
                 (recur (cons `(set-grid! ~c ~expr
                                          ~(second body))
                              result)
                        (next (next body)))
                 (recur (cons `(.add ~cntr ~expr ~c)
                              result)
                        (next body)))))))))

(defn flipper-app2 []
  ;; Construct components:
  (let [flipper (new-flipper)
        b-start (JButton. "Start")
        b-stop (doto (JButton. "Stop")
                 (.setEnabled false))
        total (text-field "0")
        heads (text-field "0")
        t-error (text-field "0.0")
        timer (Timer. 100 nil)]

    ;; Setup actions:
    (with-action timer e
      (let [state @flipper]
        (.setText total (str (:total state)))
        (.setText heads (str (:heads state)))
        (.setText t-error (format "%.10g" (error state)))))
    (with-action b-start e
      (send flipper start)
      (.setEnabled b-stop true)
      (.setEnabled b-start false)
      (.start timer))
    (with-action b-stop e
      (send flipper stop)
      (.setEnabled b-stop false)
      (.setEnabled b-start true)
      (.stop timer))

    ;; Create window and layout:
    (doto (JFrame. "Flipper")
      (.setContentPane
       (doto (JPanel. (GridBagLayout.))
         (grid-bag-layout
          :insets (Insets. 5 5 5 5)

          :gridx 0, :anchor :LINE_END
          :gridy 0, (JLabel. "Total:")
          :gridy 1, (JLabel. "Heads:")
          :gridy 2, (JLabel. "Error:")

          :gridx 1, :anchor :LINE_START
          :gridy 0, total
          :gridy 1, heads
          :gridy 2, t-error

          :gridx 0, :gridy 3, :gridwidth 2, :anchor :CENTER
          (doto (JPanel.)
            (.add b-start)
            (.add b-stop)))))
      (.pack)
      (.setVisible true))))

I centered the buttons below the text fields by embedding them in a nested JPanel that spans the full width of the window.

Run this example as:

(SwingUtilities/invokeLater flipper-app2)

Enjoy!

Heating Up Clojure & Swing

Most Swing examples don’t translate well into Clojure because they are so thoroughly embedded in the object-oriented paradigm.

A typical Swing example has a main class that extends a container class and implements some *Listener interface. Clojure beginners who try to port these examples may think they need to mimic that same structure.

In fact, there are few situations where Swing forces you to create a subclass. Most involve event listeners and can be handled adequately with Clojure’s proxy.

In this post, we’ll develop a complete, albeit small, Swing application: the classic Temperature Converter tutorial. But ours will be better. It can convert both Celsius to Fahrenheit and vice-versa, and it does the conversion immediately without waiting for a button click.

Gentleman, start your REPLs.

Start by importing all the classes we will need for this example:

(import '(javax.swing JLabel JPanel JFrame JTextField)
        '(javax.swing.event DocumentListener)
        '(java.awt GridBagLayout GridBagConstraints Insets))

Before we get to any GUI stuff, we need two functions to convert between degrees Celsius and degrees Fahrenheit:

(defn f-to-c [f]
  (* (- f 32) 5/9))

(defn c-to-f [c]
  (+ (* c 9/5) 32))

Note the use of Clojure Ratios.

Next, we need a couple of helper functions. First, the parse function will take a String typed by the user and convert it to a number. If the user types an invalid number, parse returns nil, but it can handle extra spaces:

(defn parse [s]
  (try (Double/parseDouble (.trim s))
       (catch NumberFormatException e nil)))

The display function does the opposite. It takes a number, rounds it to the nearest Integer (because Integers are prettier), and returns a String.

(defn display [n]
  (str (Math/round (float n))))

You can test these functions in the REPL:

(f-to-c 212) ;; => 100
(c-to-f 0)   ;; => 32

(parse "22.5")   ;; => 22.5
(parse " 22 ")   ;; => 22.0
(parse "foobar") ;; => nil

(display 22.5) ;; => "23"
(display 22/7) ;; => "3"

Now, time for some GUI goo!

Our temperature converter will have two text fields, one for Celsius and one for Fahrenheit, like this:

Temperature Converter GUI screenshot

As soon as the user types in either text field, the other text field will immediately change to show the converted value. So to convert Celsius to Fahrenheit, just type into the “Celsius” box. To go the other way, type into the “Fahrenheit” box.

I chose this design because it has two elements that behave very similarly, allowing me to show off some higher-order functions.

Let’s start with updating. We have two text fields. We want to update one, call it the “target” field, by converting the value of the other, call it the “source” field. But we never want to update a field while the user is typing in it! That would then trigger another update, causing an infinite loop.

Here’s the function:

(defn update-temp [source target convert]
  (when (.isFocusOwner source)
    (if-let [n (parse (.getText source))]
      (.setText target (display (convert n)))
      (.setText target ""))))

The source and target arguments are JTextFields, which we will create later. The update-temp function will be called every time one of the text fields emits a change event, so first we have to make sure that the source field (the one that triggered the event) has the keyboard focus. If it does, we try to read the source field’s contents. If parse is successful, we can calculate the value for the target field using the supplied convert function, otherwise we just set the target to be blank.

To make this work, we need to attach listeners to each of the JTextFields. We can write a function for that too:

(defn listen-temp [source target f]
  (.. source getDocument
      (addDocumentListener
       (proxy [DocumentListener] []
         (insertUpdate [e] (update-temp source target f))
         (removeUpdate [e] (update-temp source target f))
         (changedUpdate [e] )))))

Swing implements a Model-View-Controller paradigm for text fields. So to listen for changes in a text field, we actually want to listen to the Document model associated with that text field. The DocumentListener insertUpdate and removeUpdate methods are called whenever the Document changes. The changedUpdate method is not interesting to us, but we still have to provide an empty implementation in the proxy.

So now we’ve got general-purpose functions for updating one text field whenever another changes. Suppose we create two text fields named celsius and fahrenheit. Wiring them together only takes 2 lines:

(listen-temp celsius fahrenheit c-to-f)
(listen-temp fahrenheit celsius f-to-c)

And that’s exactly what you’ll see in the final app, below.

All that’s left is the layout. I’ll re-use the GridBagLayout macros from my previous post. Here they are again, for those of you following along at home:

(defmacro set-grid! [constraints field value]
  `(set! (. ~constraints ~(symbol (name field)))
         ~(if (keyword? value)
            `(. GridBagConstraints ~(symbol (name value)))
            value)))

(defmacro grid-bag-layout [container & body]
  (let [c (gensym "c")
        cntr (gensym "cntr")]
    `(let [~c (new java.awt.GridBagConstraints)
           ~cntr ~container]
       ~@(loop [result '() body body]
           (if (empty? body)
             (reverse result)
             (let [expr (first body)]
               (if (keyword? expr)
                 (recur (cons `(set-grid! ~c ~expr
                                          ~(second body))
                              result)
                        (next (next body)))
                 (recur (cons `(.add ~cntr ~expr ~c)
                              result)
                        (next body)))))))))

And, last but not least, here’s the app itself:

(defn temp-app []
  (let [celsius (JTextField. 3)
        fahrenheit (JTextField. 3)
        panel (doto (JPanel. (GridBagLayout.))
                (grid-bag-layout
                 :gridx 0, :gridy 0, :anchor :LINE_END
                 :insets (Insets. 5 5 5 5)
                 (JLabel. "Degrees Celsius:")
                 :gridy 1
                 (JLabel. "Degrees Fahrenheit:")
                 :gridx 1, :gridy 0, :anchor :LINE_START
                 celsius
                 :gridy 1
                 fahrenheit))]
    (listen-temp celsius fahrenheit c-to-f)
    (listen-temp fahrenheit celsius f-to-c)
    (doto (JFrame. "Temperature Converter")
      (.setContentPane panel)
      (.pack)
      (.setVisible true))))

Run the function (temp-app) and you’ve got yourself a temperature converter. Makes me feel all warm and GUI inside.

Taming the GridBagLayout

GUI layout is hard. You’d be crazy to do it without a GUI designer like Netbeans.

Well, I’m pretty crazy. So I’m going to do some GUI layout in Clojure. And I’m going to use the most intimidating of Java’s GUI layout classes, the GridBagLayout.

Conceptually, GridBagLayout is pretty straightforward. It places components on a flexible grid, in which each column and row is automatically sized to fit the largest component. A set of constraints placed on each component determines its exact placement, size, and alignment.

The devil, as usual, is in the details. GridBagConstraints has 11 fields and 32 constants to control the layout of each component. I won’t try to explain how it works; read the tutorial a few times instead.

The problem with GridBagConstraints, from a Clojure point of view, is that it’s a mutable object with public instance fields. This isn’t a problem for concurrency, because the object is used in only one place, but the syntax is awkward:

(import 'java.awt.GridBagConstraints)
(def c (GridBagConstraints.))
(set! (. c gridx) 1)
(set! (. c gridy) GridBagConstraints/RELATIVE)

Since I will have to do a lot of set!s, I can try to pare it down a bit with a macro:

(defmacro set-grid! [constraints field value]
  `(set! (. ~constraints ~(symbol (name field)))
         ~(if (keyword? value)
            `(. java.awt.GridBagConstraints
                ~(symbol (name value)))
            value)))

This macro takes a field name as a keyword and sets the value of that field. I used keywords instead of bare symbols because they tend to signal names or constants in Clojure code.

The macro has one other trick up its sleeve: if the value of a field is a keyword, it gets used as the name of a static field (constant) in GridBagConstraints.

With this macro, the set!s in the previous example become:

(set-grid! c :gridx 1)
(set-grid! c :gridy :RELATIVE)

So far, so good. But we’ve only replaced a bunch of set!s with a bunch of set-grid!s.

What we really want is a terse syntax for specifying constraints. There are many ways to do this. I could write a macro that creates a new GridBagConstraints for each component. But that would require a lot of repetition.

Often one wants to reuse the same constraint for several components in a row. The tutorial examples achieve this by using a single instance of GridBagConstraints and modifying its fields for each component. (The definition of GridBagLayout explicitly permits this.)

So what I want is a macro that allows me to add components to a container, in any order, specifying only the constraints that need to change for each component. Here’s what it will look like:

(grid-bag-layout container
  :gridx 0, :gridy 0
  component-one
  :gridx :RELATIVE, :gridwidth 2
  component-two
  ;; ... more components & constraints ...
  )

The first argument to the macro is a container with a GridBagLayout as its layout manager. What follows is a mixture of components and constraints. Each component is added to the layout with the current set of constraints. A keyword signals a change to a constraint field, and is immediately followed by its value. Once a field is set, it retains its value until it is set again.

The line breaks and commas are just whitespace; what matters is the order.

Here’s the macro:

(defmacro grid-bag-layout [container & body]
  (let [c (gensym "c")
        cntr (gensym "cntr")]
    `(let [~c (new java.awt.GridBagConstraints)
           ~cntr ~container]
       ~@(loop [result '() body body]
           (if (empty? body)
             (reverse result)
             (let [expr (first body)]
               (if (keyword? expr)
                 (recur (cons `(set-grid! ~c ~expr
                                          ~(second body))
                              result)
                        (next (next body)))
                 (recur (cons `(.add ~cntr ~expr ~c)
                              result)
                        (next body)))))))))

You’ll have to take my word for it that this macro was not especially difficult to write. As for what it does, it loops through the body and recursively constructs code for the result. When it encounters a keyword, it uses the set-grid! macro I defined earlier. Otherwise, it assumes the expression is a component, and adds it to the container. (The manual gensyms are necessary because of the nested backquotes.)

Here’s an example that creates a layout with three buttons, as in this screenshot:

GridBagLayout example

(import '(javax.swing JFrame JPanel JButton)
        '(java.awt GridBagLayout Insets))

(def panel
     (doto (JPanel. (GridBagLayout.))
       (grid-bag-layout
        :fill :BOTH, :insets (Insets. 5 5 5 5)
        :gridx 0, :gridy 0
        (JButton. "One")
        :gridy 1
        (JButton. "Two")
        :gridx 1, :gridy 0, :gridheight 2
        (JButton. "Three"))))

(def frame
     (doto (JFrame. "GridBagLayout Test")
       (.setContentPane panel)
       (.pack)
       (.setVisible true)))

Admittedly, this is not all that much shorter than the equivalent Java code. But it’s still shorter, without diminishing the power or flexibility of the original API.

This is the kind of mini-language for which Lisp is famous. And it’s only the beginning. We could go on to define a more complete, expressive, and functional language for designing GUIs. But that will have to wait for another post.

doto Swing with Clojure

One of the great things about Clojure is how it can make Java programming easier and less verbose.

Take Swing. It takes a ton of code to render even a simple GUI. Most tutorials don’t even tackle it without an IDE like NetBeans.

But we’ve got something Java lacks: macros!

In this post, I’ll build a simple counter application, using Clojure macros to make the code shorter and simpler.

Our app has two components: a label showing the current value of the counter, and a button to increment the counter. Here’s the basic structure:

(import '(javax.swing JLabel JButton JPanel JFrame))

(defn counter-app []
  (let [label (JLabel. "Counter: 0")
        button (JButton. "Add 1")
        panel (JPanel.)
        frame (JFrame. "Counter App")]
    (.setOpaque panel true)
    (.add panel label)
    (.add panel button)
    (.setContentPane frame panel)
    (.setSize frame 300 100)
    (.setVisible frame true)))

You can run counter-app at the REPL and see the resulting GUI layout, although the button doesn’t do anything yet.

The annoying thing about this code is the imperative style Swing forces on us: construct local variables and hammer at them with method calls.

Fortunately, Clojure has a handy built-in macro for just this kind of situation: doto. The doto macro takes a body of expressions. It evaluates the first expression and saves it in a temporary variable, and then inserts that variable as the first argument in each of the following expressions. Finally, doto returns the value of the temporary variable. An example will make more sense:

;; This code:
(doto (make-thing)
 (foo 1 2)
 (bar 3 4))

;; Expands to this:
(let [x (make-thing)]
 (foo x 1 2)
 (bar x 3 4)
 x)

The object created on the first line gets threaded through each of the following expressions and returned at the end.

We can use this to clean up our counter-app code:

(defn counter-app []
  (let [label (JLabel. "Counter: 0")
        button (JButton. "Add 1")
        panel (doto (JPanel.)
                (.setOpaque true)
                (.add label)
                (.add button))]
    (doto (JFrame. "Counter App")
      (.setContentPane panel)
      (.setSize 300 100)
      (.setVisible true))))

Notice that we have eliminated one local variable (frame) entirely. Furthermore, all the expressions dealing with the JPanel are neatly grouped together.

For this to work out neatly, the order of definitions is important. We start at the inner-most components, JLabel and JButton, and move outward to the containing window.

Moving on! In my last post, I showed you how to proxy ActionListener to handle events like button clicks. Rather than typing out the proxy code each time, let’s make a macro:

(defmacro on-action [component event & body]
  `(. ~component addActionListener
      (proxy [java.awt.event.ActionListener] []
        (actionPerformed [~event] ~@body))))

The on-action macro’s first argument is any component (such as JButton) that has an addActionListener method. The body of the macro is the code that will be executed when the ActionListener is triggered. The event argument is just a symbol; it will be bound to the ActionEvent that triggered the listener. (We could have used a fixed symbol like “this”, but that would be bad macro design.)

With this macro, the definition of our JButton can look like this:

(doto (JButton. "Add 1")
  (on-action event
    ;; ... code to run when button is clicked ...
  ))

We’re almost done! We just need a place to store the current value of the counter. Since we’re not worried about synchronization at this point, we can use an atom:

;; Initialize the counter
(let [counter (atom 0)]
  ;; ... later on ...
  ;; Update the counter:
  (swap! counter inc))

Bringing it all together, our final app looks like this:

(defn counter-app []
  (let [counter (atom 0)
        label (JLabel. "Counter: 0")
        button (doto (JButton. "Add 1")
                 (on-action evnt  ;; evnt is not used
                   (.setText label
                      (str "Counter: " (swap! counter inc)))))
        panel (doto (JPanel.)
                (.setOpaque true)
                (.add label)
                (.add button))]
    (doto (JFrame. "Counter App")
      (.setContentPane panel)
      (.setSize 300 100)
      (.setVisible true))))

Run counter-app at the REPL and you have a working GUI application. Not bad for about 50 lines!

Swing Into Actions with Clojure

My previous post left you with a Clojure/Swing GUI consisting of one window and one button. Boring! Let’s make it do something.

To catch up, start a Clojure REPL and type:

(import '(javax.swing JFrame JPanel JButton))
(def button (JButton. "Click Me!"))
(def panel (doto (JPanel.)
             (.add button)))
(def frame (doto (JFrame. "Hello Frame")
             (.setSize 200 200)
             (.setContentPane panel)
             (.setVisible true)))

Boom, one window-and-button on the screen.

Let’s make our button do something. First, we’ll define a function for what we want to do:

(import 'javax.swing.JOptionPane)
(defn say-hello []
  (JOptionPane/showMessageDialog
    nil "Hello, World!" "Greeting"
    JOptionPane/INFORMATION_MESSAGE))

You can call the say-hello function directly; it pops up a dialog box, using the utilities in JOptionPane.

To connect this function to our button, we have to provide a class implementing the ActionListener interface. Clojure’s proxy feature is the easiest way to do this:

(import 'java.awt.event.ActionListener)
(def act (proxy [ActionListener] []
           (actionPerformed [event] (say-hello))))

Now act is an instance of an anonymous class implementing the actionPerformed method. We can attach this class as a listener of our button:

(.addActionListener button act)

And we’re done! Click the button, and a dialog box pops up.

First Steps With Clojure & Swing

Swing is the GUI standard for Java. Clojure is the awesomeness standard for Java. Let’s make an awesome GUI.

Make a Window

Interactive development is fun. Fire up a Clojure REPL, and type this:

(import 'javax.swing.JFrame)
(def frame (JFrame. "Hello Frame"))
(.setSize frame 200 200)
(.setVisible frame true)

Hey Presto, there’s a window! (It might not pop to the front, so check your task bar.)

JFrame is Swing’s all-purpose window class. This example created a frame, set its dimensions to 200×200 pixels, and “turned it on” by calling setVisible.

Containers and Frames

Our new frame doesn’t look like much; let’s give it some content. More specifically, let’s give it a container. Swing GUIs are laid out as a nested hierarchy of containers. All containers — except the top-level window — are sub-classes of JComponent. This is called the containment hierarchy.

Although it’s technically possible to add GUI elements directly to a top-level container like JFrame, it’s more correct to use a content pane. We’ll use JPanel, a general-purpose container:

(import 'javax.swing.JPanel)
(def panel (JPanel.))
(.setContentPane frame panel)

A panel by itself doesn’t show anything, so lets make a button and add it to the panel.

(import 'javax.swing.JButton)
(def button (JButton. "Click Me!"))
(.add panel button)

Hey, it’s not there! That’s because Swing wasn’t designed with interactive development in mind. To make your button visible, call:

(.revalidate button)

The revalidate method is not something you’ll read about in most Swing tutorials, because in pre-compiled Java it’s rarely necessary. Basically, it tells Swing, “I just changed the layout, you need to redraw stuff.” Starting at our JButton, Swing searches up the containment hierarchy to the top-level container, and redraws it.

Next step: Action! My next post will talk about enabling GUI events with ActionListener.

Objects Are Not Abstract Data Types

I was lucky enough to see a talk by Barbara Liskov, the grande dame of computer science. The talk was titled “The Power of Abstraction,” and it covered Liskov’s work on programming languages in the 1970s and 1980s, primarily a language called CLU.

Update 1/14/2010: Video of the same talk is available here: OOPSLA Keynote: The Power Of Abstraction

CLU had a number of interesting features that were ahead of its time — heap-based garbage collection, typed exceptions, and iterators. Many of these features made their way into object-oriented languages such as Java. But CLU itself is not object-oriented.

Object-oriented languages, Liskov said, tend to conflate the concrete representation of a type with the interface used to access it. Think of a classic Java class in an introductory OOP text. The class contains both instance fields and methods to manipulate them. Even though the fields are private, the interface is tied to a specific implementation. You can’t substitute a different implementation, not even by subclassing.

CLU provides separate structures for fields and methods. Fields are defined in types, which are more or less like C structs. Methods are defined in clusters, from which the name CLU derives. A cluster is a named set of method implementations, associated with one particular type. Users only work with clusters, not types. A cluster may be substituted by a another cluster that implements the same methods.

Why is this interesting now? Because we’re just catching up to where Liskov was in the seventies. Modern Java designs often favor interface-based APIs with no concrete inheritance and no public constructors.

This is even more interesting to me, because my favorite programming language will soon have features very similar to CLU’s types and clusters. The “new” branch of Clojure defines two new abstractions: datatypes and protocols.

A protocol is a set of function signatures, with no implementation. Conceptually, it’s similar to a Java interface. You could use a protocol to define an API to model some real-world object, such as Employee, Department, etc.

A datatype is a set of named fields, with optional type declarations. Conceptually, it’s similar to a C struct. However, a datatype can also declare support for any number of protocols, and supply methods to implement those protocols. For example, Clojure will probably have a Countable protocol with a single method count. Clojure datatypes like Lists and Vectors can provide their own implementations of count. At that level, the datatype is like a concrete class implementing several interfaces.

What’s really cool is that you can extend protocols for existing types, even Java classes. So, for example, we could implement Countable for java.lang.String by writing a count method that calls String.length(). This means you can create new protocols for Java classes that you do not control. This is like interface injection, a proposed but as-yet unimplemented feature for Java.

Protocol method calls are dispatched dynamically based on the type of their first argument, very similar to (and at the same speed as) Java method calls.

Impedence Mismatch

Data formats are annoying. As much as half the code in any large software project consists of translating from one data representation — objects, SQL tables, files, XML, RDF, JSON, YAML, CSV, Protocol Buffers, Avro, XML-RPC — to another.

Each format has its own strengths and weaknesses. Often, no single representation is complete enough to be considered “canonical.” The only canonical representation is an abstract one, a platonic ideal in the mind of some developer. Since this platonic ideal cannot be implemented in code, different people have different expectations for how a particular model is supposed to work.

There are two options: Either you re-implement the model, with all its features and constraints, for each format, and hand-code all the translations; or you use a “smart” library that automatically translates between different representations. ActiveRecord and Hibernate are popular examples of the latter.

The problem with “smart” libraries is that they can never be smart enough. At some point you always have to dig into the generated SQL or whatever to make them work efficiently, or even correctly. Frequently this is impossible without hacking the library sources, a daunting tangle of generated and meta-programmed code. The library that was supposed to make your life easier instead makes it hell.

Do these “smart” libraries really save any time? Would it be easier to just write the translation code in the first place? We’ll never know, because programmers can’t resist “smart” systems, the myth that you can “do more with less code.” You can never do more with less, unless what you’re doing is the lowest common denominator of what everyone else is doing. And if that is what you’re doing, then why bother?

Generating Clojure from an Ontology

I’ve been fascinated with RDF for years, but I always end up frustrated when I try to use it. How do you read/write/manipulate RDF data in code? Sure, there are lots of libraries, but they all represent RDF data as its primitive structures: statements, resources, literals, etc. Working with data through these APIs feels like using a glovebox. To get anything useful done, you have to define mappings between RDF properties/classes and normal data structures in your programming language — classes, maps, lists, whatever. In effect, you have to define everything twice.

Some Java APIs allow one to add annotation properties to classes and methods, with the annotations defining the mapping between Java objects and RDF triples. It’s convenient, and familiar if you’ve used Java persistence frameworks like Hibernate, but you still have to define everything twice — once in your RDF schema, once in Java code.

Other libraries generate Java source code from RDFS or OWL ontologies. This means you don’t have to define everything twice, but adds another step to the write-compile-run cycle, and limits you to the semantics that the code generator can understand. In particular, certain features of RDFS/OWL — multiple inheritance, sub-properties — do not map well into Java.

What I really wanted was a way to create and work with RDF data in Clojure, using the same map/set/sequence APIs that I use for any other Clojure data structure. I flirted with implementing RDF in Clojure but lost interest when I realized that 1) there’s a lot more to implementing RDF than datatype conversions; and 2) my Clojure library suffered from the same glovebox problem as the Java RDF libraries.

The solution, however, was staring me in the face all along. Clojure is a Lisp. I can generate functions directly, without any intermediate “source” representation. I can use my own customized validation and type-checking functions. Furthermore, I can extend the definitions in my RDF schema with new Clojure functions.

Here’s what I ended up with: I designed a simple OWL ontology using Protege 4 and saved it as RDF/XML. Then I used the Sesame 2 library to find all the RDF classes and properties defined in my ontology, and create the appropriate getter, setter, and constructor functions in Clojure. It looks something like this:

(defn intern-classes [] 
  (doseq [cls (find-all-classes *ontology*)]
    (let [name (resource-to-symbol cls)]
      (intern *ns* name (fn [] {:type name})))))

The resource-to-symbol function creates a symbol named for the local name of the RDF class, with the full URI of its XML namespace in the symbol’s metadata. The call to intern defines a new function that takes no arguments and returns a Clojure map with the symbol as its :type.

Suppose I have a class named Document in my ontology. I now have a Clojure function named Document that creates a new instance of that class, represented as a Clojure map. Furthermore, using Clojure hierarchies and the isa? function, I can generate Clojure code that implements the subclass relationships defined in the ontology. Whee!

I don’t entirely know where I’m headed with this, but I like the way it’s going. I can define my own data types, decide how they map to Clojure data structures, and have code that’s always up-to-date with my RDF vocabulary.