Mutual Recursion demo in Rust and Racket (inspired by Haskell)

This is a quick post on a Rust version of the Haskell evens and odds program demonstrating mutual recursion (as shown in Hutton’s book).

First off, the Haskell code:

  evens :: [a] -> [a]
  evens [] = []
  evens (x:xs) = x : odds xs

  odds :: [a] -> [a]
  odds [] = []
  odds (_:xs) = evens xs

A sample run:

*Main> let string = "abcde"
*Main> evens string
"ace"
*Main> odds string
"bd"
*Main> string
"abcde"

So the whole ideas is to have the evens functions display all the characters in even positions (starting from 0), and then odds function likewise display all the characters in odd positions.

The evens function acts as the actual accumulator whilst odds is only used as a trampoline for continuing the recursion.

Now, for a rough Rust version of it (preserving the original character array):


fn main() {
    fn evens<T: Copy>(xs: &[T]) -> Vec<T> {
        if xs.is_empty() {
            Vec::new()
        } else {
            cons(&xs[0], &odds(&xs[1..]))
        }
    }

    fn odds<T: Copy>(xs: &[T]) -> Vec<T> {
        if xs.is_empty() {
            Vec::new()
        } else {
            evens(&xs[1..])
        }
    }

    fn cons<T: Copy>(x: &T, xs: &[T]) -> Vec<T> {
        let mut vec = Vec::new();

        vec.push(*x);

        for e in xs.iter() {
            vec.push(*e);
        }
        vec
    }

    let string = String::from("abcde");

    println!("{}",
             String::from_utf8(evens(&string.clone().into_bytes())).unwrap());
    println!("{}",
             String::from_utf8(odds(&string.clone().into_bytes())).unwrap());

    println!("{}", string);
}

And a quick run:

Macushla:EvensAndOdds z0ltan$ rustc evens_and_odds.rs
Macushla:EvensAndOdds z0ltan$ ./evens_and_odds
ace
bd
abcde

So, as can be clearly seen, the original string is left unmodified. Of course this version looks quite dirty, but the nice bit is that &[T] accepts parameters of type Vec (or reference variants) and vice-versa. This enables using slicing extensively and naturally inside the functions. The vector copying code could, of course, be made to work with an API call, but I feel this is much better in its explicit form.

The Racket version looks much nicer, being more amenable to functional constructs than Rust:

#lang racket

(define (evens xs)
  (if (null? xs)
      '()
      (cons (car xs) (odds (cdr xs)))))

(define (odds xs)
  (if (null? xs)
      '()
      (evens (cdr xs))))

(define (main)
  (let ([string "abcde"])
    (displayln (list->string (evens (string->list string))))
    (displayln (list->string (odds (string->list string))))
    (displayln string)))

And a final run for the Racket version:

evens-and-odds.rkt> (main)
ace
bd
abcde

A simple letn macro in Racket

A long time back I had written a small blog about a ‘letn’ macro in Common Lisp (check it out here). Of late, I have been venturing deeper and deeper into Racket, and I am starting to like the language, and more importantly, the ecosystem more and more, especially with the express purpose of implementing languages and expanding my understanding of programming language theory.

This is why I decided to give the letn macro a go in Racket this time. Of course, this may by no means be the best way to implement it, but it was an enjoyable exercise all the same. The basic idea is to transform a form like:

   (letn [a 1 b 2 c 3]
       (+ a b c))

into the corresponding syntactic form:

   (let ([a 1]
         [b 2]
         [c 3])
      (+ a b c))

The only difference between this version and the Common Lisp version, functionally speaking, is that in this version, I expect the input to be well-formed pairs of variables and values. This makes more sense now since we cannot possibly substitute a sane value for a variable with no associated value (null? 0? void?), and expect a sane result.

Anyway, so here’s how it looks:

;;; a letn macro in Racket.

(module letn racket
  (provide letn)


;;; (letn [a 1 b 2 c 3 d 4 e 5 f 6] (+ a b c d e f)) ->
;;;
;;; (let ([a 1]
;;;       [b 2]
;;;       [c 3]
;;;       [d 4]
;;;       [e 5]
;;;       [f 6])
;;;    (+ a b c d e f))


(require (for-syntax racket/list)) ;; for empty

(begin-for-syntax
  (define (process-args-into-pairs lst)
    (letrec ([f (lambda (pairs lst)
                  (if (null? lst)
                      (reverse pairs)
                      (f (cons (list (car lst) (cadr lst)) pairs) (cddr lst))))])
      (f empty lst))))


(define-syntax letn
  (lambda (stx)
    (syntax-case stx ()
      [(_ (params ...) body0 body ...)
       (let ([pairs (process-args-into-pairs (syntax->datum #'(params ...)))])
         (with-syntax ([arg-pairs (datum->syntax stx pairs)])
           #'(let arg-pairs
                 body0 body ...)))]))))

Some notes

: Okay, so begin by defining the macro in a module of its own. Then we come to this interesting snippet of code”

    (require (for-syntax racket/list)) ;; for empty

What this code means is that we wish to use the racket/list module during compilation-time (since macro-expansion is part of the compilation phase). The reason for this is that we use empty, which denotes an empty list, in our program. Of course it would be easier to simply use the literal form, '() and eschew requiring racket/list altogether, but this is simply to demonstrate how we can require modules whose functions and symbols we would need at compile time.

Next up, we have the following code block:

(begin-for-syntax
  (define (process-args-into-pairs lst)
    (letrec ([f (lambda (pairs lst)
                  (if (null? lst)
                      (reverse pairs)
                      (f (cons (list (car lst) (cadr lst)) pairs) (cddr lst))))])
      (f empty lst))))

The begin-for-syntax starts off a new block where we can define functions that we need during compile time itself. In this case, we need a helper function called process-args-into-pairs which simply takes an input of the form

'(a 1 b 2 c 3 d 4 e 5)

and transforms those into a list of lists:

 '((a 1) (b 2) (c 3) (d 4) (e 5))

This is precisely what the actual macro needs during its expansion. Note that since we only have one helper function in this case, we could have used the simpler version, define-for-syntax to define our helper function like so:

    (define-for-syntax (process-args-into-pairs lst)
        (letrec ([f (lambda (pairs lst)
                      (if (null? lst)
                          (reverse pairs)
                          (f (cons (list (car lst) (cadr lst)) pairs) 
                             (cddr lst))))])
              (f empty lst))))

The process-args-into-pairs helper function itself is extremely straightforward – we simply accumulate lists of pairs of objects from the input list, and then return them to the caller. This code works on the understanding (as mentioned before) that we expect the input to consist of well-formed pairs).

Now let’s get down to the meat of the business, the letn macro itself. Here is the code:

(define-syntax letn
  (lambda (stx)
    (syntax-case stx ()
      [(_ (params ...) body0 body ...)
       (let ([pairs (process-args-into-pairs (syntax->datum #'(params ...)))])
         (with-syntax ([arg-pairs (datum->syntax stx pairs)])
           #'(let arg-pairs
                 body0 body ...)))]))))

There are various ways of defining macros in Racket – define-syntax-rule, define-syntax with syntax-rules,, define-syntax with syntax-case, define-syntax with custom transformer functions, syntax-parse,etc.

In this case, I have decided to use syntax-case since it suits the requirements quite nicely – built-in pattern matching is quite nifty!

So here’s how it works – we pattern-match on the supplied syntax (object), and we expect the pattern to be of the form: (letn [*] *). Note that in Racket, square brackets are essentially equivalent to (and are converted to, internally) parentheses. As a side-note, when entering code, however, mixing square brackets and parentheses for the same form is an error.

In the template (the right-hand-side of this case), we bind pairs to the output of the process-args-into-pairs helper function. Remember that all this happens during compile-time itself. Also note that we need to pass a plain list to the helper function. This is the reason why we need to convert the syntax object into a proper datum (done using (syntax->datum #'(params ...)).

Next, we need to construct the actual form that the invocation of the macro will expand into. In Common Lisp, we do all that using quasi-quoting and unquoting (with splicing if needed). However, in Racket, we have a different set of forms that deal with this business. The helper function returns a list of lists of variable-value pairs, and this list needs to be inserted into the let form that we use for the actual body of the template. This is why we need to convert pairs into a syntax object (since Racket works with syntax objects directly almost throughout). This is why we have
(datum->syntax stx pairs).

Finally, we now return the syntax from the template. Note the reader macro, #' which is shorthand for syntax.

Well, that’s about it! In macro, defining recursive macros is pretty easy using ellipses (...). This is used throughout for both the parameters and the body forms of the macro invocation. This also conveniently ensures that we can nest arbitrary forms inside out stonking new letn macro.

All right, let’s take it for a quick spin:

Here is the test code:

#lang racket

(require "letn.rkt")

(define (test-case-1)
  (letn [a 1 b 2]
        (displayln (+ a b))))

(define (test-case-2)
  (letn (a "hello" b "world")
        (displayln (string-append a ", " b))))


(define (test-case-3)
  (letn (a 1 b 2 c 3)
        (displayln "Adding three numbers")
        (displayln (+ a b c))))


(define (test-case-4)
  (letn (a 1 b 2 c 3)
        (letn (d 4 e 5)
              (displayln "Adding nested variables")
              (displayln (+ a b c d e)))))

(define (test-case-5)
  (letn (a 1 b 2 c 3)
        (let ([d 4]
              [e 5])
          (letn (f 6 g 7)
                (displayln "Nested letnS and letS")
                (displayln (+ a b c d e f g))))))

(define (run-all-tests)
  (test-case-1)
  (newline)
  (test-case-2)
  (newline)
  (test-case-3)
  (newline)
  (test-case-4)
  (newline)
  (test-case-5))  

And here is the output of a test run:

letn-test.rkt> (run-all-tests)
3

hello, world

Adding three numbers
6

Adding nested variables
15

Nested letnS and letS
28

Excellent! This was quite a satisfying little exercise. Now time to up the ante and start off with real languages!

A PigLatin translator in Racket

This post was inspired by a question posted on /r/programming on reddit. As part of helping the person, I realised I could create one just for fun in Racket!

I started out by reading the rules for Pig Latin on Wikipedia (dead simple rules), and the only irksome bit was ensuring that the capitalisation of the words remained intact. Also, the input and output formats were inspired by the posted question (it would have been much simpler to process a list of strings, or even a string of words directly).

Here is the code, followed by a bit of explanation.

(module piglatin racket
  (provide translate)

(define (translate sentence)
  (map string->symbol
       (map english->piglatin
           (map string->list
                (map symbol->string sentence)))))


(define (english->piglatin word)
  (if (starts-vowel? word)
      (word->vowel-rule word)
      (word->consonant-rule word)))


(define (starts-vowel? word)
  (member (char-downcase (car word)) '(#\a #\e #\i #\o #\u #\y)))


(define (word->vowel-rule word)
  (string-append (list->string word) "way"))


(define (word->consonant-rule word)
  (let [(was-capital? (char-upper-case? (car word)))]
    (letrec [(f (lambda (word)
                 (if (starts-vowel? word)
                     (cond [was-capital? (string-titlecase
                                          (string-append (list->string word)                  "ay"))]
                            [else (string-append (list->string word) "ay")])
                      (f (append (cdr word)
                                 (list (char-downcase (car word))))))))]
      (f word)))))

Explanation:

Let’s break down the code into chunks for easier explanation.

The input format is a list of symbols (not strings) such as: '(hello world). As such I figured that it was best to do some top-down programming here. To that end, the main function (and the only one exposed to the outside world) is the translate function:

(define (translate sentence)
  (map string->symbol
       (map english->piglatin
           (map string->list
                (map symbol->string sentence)))))

What I’m doing here is taking the input, sentence, which is in the specified format, and then I convert that into a list of strings, followed by converting that to a list of list of characters (Racket does not parse strings as lists of characters directly, like Haskell does). Following that, I convert each word in this list to its corresponding PigLatin form, and since the output format is again a list of symbols, map the strings back to symbols.

Then we have basically two rules – one for words that begin with vowels, and another one for words that begin with consonants.

(define (english->piglatin word)
  (if (starts-vowel? word)
      (word->vowel-rule word)
      (word->consonant-rule word)))

The starts-vowel? predicate simply checks if the word begins with a vowel or not (we convert the letter to lowercase for easier checking)

(define (starts-vowel? word)
  (member (char-downcase (car word)) '(#\a #\e #\i #\o #\u #\y)))

The rule for words beginning with a vowels is simply to append a “way” to the string:

(define (word->vowel-rule word)
  (string-append (list->string word) "way"))

For words that begin with consonants though, the rule is a bit more involved. Basically, we have to extract the consonant cluster (one or more letters) at the beginning of the word, append that to the end of the updated word (which now begins with a vowel), and also suffix an “ay” at the end. Note that we also have to take care of proper capitalisation in this case, which we didn’t have to do with the vowel rule:

define (word->consonant-rule word)
  (let [(was-capital? (char-upper-case? (car word)))]
    (letrec [(f (lambda (word)
                 (if (starts-vowel? word)
                     (cond [was-capital? (string-titlecase
                                          (string-append (list->string word)                  "ay"))]
                            [else (string-append (list->string word) "ay")])
                      (f (append (cdr word)
                                 (list (char-downcase (car word))))))))]
      (f word)))))

As you can see, since we are performing recursion to extract the consonant cluster, we maintain the original capitalisation of the word in a local binding called was-capital?. Then we recurse through the word, and in case was-capital> is true, we use the string-titlecase function to capitalise the first letter of the processed word. Note that we could have managed without using this built-in function, but the increase in verbosity for this little gain hardly seems worth the effort.

All right, let’s test it out on a variety of input cases:

> (load "pig-latin.rkt")
> (require 'piglatin)
> (translate '(My))
'(Ymay)
> (translate '(My hovercraft is full of eels))
'(Ymay overcrafthay isway ullfay ofway eelsway)
> (translate '(Always the odd one out))
'(Alwaysway ethay oddway oneway outway)
> (translate '(sticks and stones))
'(icksstay andway onesstay)
> (translate '(Hello world we meet again))
'(Ellohay orldway eway eetmay againway)
>(translate '(Cucullus non facit monachum)) 
'(Uculluscay onnay acitfay onachummay)
> (translate '(The quick brown fox jumped over the lazy dog))
'(Ethay uickqay ownbray oxfay umpedjay overway ethay azylay ogday)
> (translate '(Allo allo))
'(Alloway alloway)


This sort of stuff is what makes dynamic languages so dear to me, especially for prototyping. If I had done it in a static language, it would have taken quite a bit more effort (type inference is wonderful, but it does not actually save you from wrestling with the type system!)

A small vector initialisation macro in Rust

Learning Rust’s macros was almost a sort of déjà vu for me. It is remarkably similar to the new-fangled macro system used in Racket. In the first place, Racket macros are themselves quite different (syntactically and semantically) from Common Lisp macros (which I love, but I have to admit that Racket macros are much more user-friendly), and so it was quite surprising to see Rust’s macro-rules! are almost identical to Racket’s syntax-rules, including the Pattern Matching, and of course, hygiene.

I doubt that’s an historical accident, of course, but the funny bit is that it only adds to Rust’s deep heritage of borrowing not only semantics, but also syntax from other languages (I have already seen traces of SML and Haskell, and now Racket). Nevertheless, the best part for me was that it’s helping me pick up Rust’s macros quite quickly and easily (not an expert by any means), including recursive macros (which are, admittedly, rather difficult to grok in Common Lisp).

So in this short blog, I wanted to post a small macro that I wrote as part of my ongoing study of Rust. It is a simple vector initialisation macro. All this macro does is to take in a binding of the form:

let some_vec = init_vec![size; init_value];

where size determines how many elements we want in the vector, and init_value determines what value the entire vector will be initialised with.

At this juncture, it would be probably be wise to mention another aspect of Rust’s macros that pleasantly surprised me – in the macro call shown above, the square brackets can actually be replaced by a pair of parentheses, or even a pair of flowery brackets (or braces as some folks call them). This is again very similar to Racket’s behaviour. However, we can mix two different styles of brackets. Just to clarify this further, the following three are identical:

let some_vec = init_vec![size; init_value];
let some_vec = init_vec!(size; init_value);
let some_vec = init_vec{size; init_value};

However, something like the following is illegal:

let some_vec = init_vec!{size; init_value];

Also, before showing the code, it is equally interesting to note that the rule also applies to the definition of the macro itself. Instead of flowery brackets, we could as well have chosen to use parentheses to wrap the rule in. In fact, that would even be my preferred style since Common Lisp has made me more or less immune to parentheses! (only half-joking).

Here is the macro and some test code for it:

/// Here we demonstrate a macro that takes in a size, and an init value
/// and returns a vector of that size initialised with the init value.

use std::fmt::Debug;
use std::fmt::{Display, Formatter, Result};

// the main man!
macro_rules! init_vec {
	( $size: expr; $init: expr ) => { {
			let mut temp_vec = Vec::new();

			for _ in 0..$size {
				temp_vec.push($init);
			}

			temp_vec
		};
	} // block necessary here
}

// a custom structure
#[derive(Debug)]
struct Foo {
	bar: f64,
}

impl Foo {
	fn new() -> Foo {
		Foo {
			bar: 0.0,
		}
	}
}

impl Display for Foo {
	fn fmt(&self, f: &mut Formatter) -> Result {
		write!(f, "{{ bar: {} }}", self.bar)
	}
}


fn print_vec<T: Debug + Display>(name: &str, vec: &Vec<T>) {
	println!("{} = {:?}", name, vec);

	print!("The contents are... ");

	for e in vec.iter() {
		print!("{} ", *e);
	}
	println!("\n");
}


fn main() {
	let int_vec = init_vec![10; 99];
	print_vec("int_vec", &int_vec);

	let str_vec = init_vec![5; "hello"];
	print_vec("str_vec", &str_vec);
	
	let mut foo_vec = init_vec![7; Foo::new()];
	print_vec("foo_vec", &foo_vec);

	// we can also use it like any normal vector
	foo_vec[0].bar = 100.0;
	foo_vec[3].bar = 2.71828;
	foo_vec[5].bar = 3.14159;

	println!("After mutation...\n");

	print_vec("foo_vec", &foo_vec);
}

Let’s take it for a quick run:

int_vec = [99, 99, 99, 99, 99, 99, 99, 99, 99, 99]
The contents are... 99 99 99 99 99 99 99 99 99 99 

str_vec = ["hello", "hello", "hello", "hello", "hello"]
The contents are... hello hello hello hello hello 

foo_vec = [Foo { bar: 0 }, Foo { bar: 0 }, Foo { bar: 0 }, Foo { bar: 0 }, Foo { bar: 0 }, Foo { bar: 0 }, Foo { bar: 0 }]
The contents are... { bar: 0 } { bar: 0 } { bar: 0 } { bar: 0 } { bar: 0 } { bar: 0 } { bar: 0 } 

After mutation...

foo_vec = [Foo { bar: 100 }, Foo { bar: 0 }, Foo { bar: 0 }, Foo { bar: 2.71828 }, Foo { bar: 0 }, Foo { bar: 3.14159 }, Foo { bar: 0 }]
The contents are... { bar: 100 } { bar: 0 } { bar: 0 } { bar: 2.71828 } { bar: 0 } { bar: 3.14159 } { bar: 0 } 

Excellent! So it all works pretty much as expected. The code probably merits a bit of explanation – in the macro, we simply define a rule which expects an expression ( $size: expr), followed by a semi-colon, followed by another expression ($init: expr).

Note that expr has a special meaning in Rust. It is what is called a “designator” and defines the type of the data being passed in. There are various such designators available (ident for identifiers. type for types, etc. Refer to the documentation for further details).

So the whole ( $size: expr; $init: expr ) denotes the pattern that, if matched, leads to the logic on the right-hand side of the =>. Now, the right hand-side is where all the action takes place. All we do there is to create a temporary vector, and then insert as many init values as size inside the vector, and finally return the vector. Since there are multiple expression/statements in the rule, we safely ensconce them within a block using the flowery brackets. Note that there is really no type-checking done inside to see if size is a valid numeric type. This may not be possible since macro-expansion should happen very early in the compilation phase. However, I might be wrong (as many times before!), and if I come across such means, I will update this blog accordingly.

So, it was a quick little fun exercise, and it makes Rust so much more appealing to me now especially since it’s been some time since I’ve played around with macros in Common Lisp. Maybe one of these days, eh?

Hoyte’s Line Number closure in a few choice languages

Douglas Hoyte, in his excellent (if a bit fanatical) book, “Let over Lambda” gives a simple and pithy example to demonstrate the concept of closures – little anonymous functions that can capture variables in the environment in which the closure was created.

The example is very simple – create a mini-logging facility by capturing a variable representing the current line number (initially set to 0), incrementing it for every invocation of the closure, and printing it out.

An implementation in Common Lisp might look so –

(defun get-line-logger ()
  (let ((line-num 0))
    #'(lambda (id)
        (incf line-num)
        (format t "[~a] Line number: ~d~%" id line-num))))


(defun logger-demo ()
  (let ((logger-1 (get-line-logger))
        (logger-2 (get-line-logger)))
    (flet ((f (id logger)
             (dotimes (i 5)
               (funcall logger id))
             (terpri)))
      (f "logger-1" logger-1)
      (f "logger-2" logger-2))))

Sample run:

CL-USER> (logger-demo)
[logger-1] Line number: 1
[logger-1] Line number: 2
[logger-1] Line number: 3
[logger-1] Line number: 4
[logger-1] Line number: 5

[logger-2] Line number: 1
[logger-2] Line number: 2
[logger-2] Line number: 3
[logger-2] Line number: 4
[logger-2] Line number: 5

NIL

As expected, we can not only capture local variables in the lexical environment during the time of the closure’s creation, but also modify them independently of any other instances of the closure. This is what makes is a proper closure. Also note that the capture is automatically done (whether we actually use the variables or not is irrelevant).

The Racket version is, unsurprisingly, almost identical not only in syntax, but also semantics:

#lang racket

(define (get-line-logger)
  (let ([line-no 0])
    (lambda (id)
      (set! line-no (+ 1 line-no))
      (fprintf (current-output-port)"[~a] Line number: ~a~%" id line-no))))

(define (logger-demo)
  (let ([logger-1 (get-line-logger)]
        [logger-2 (get-line-logger)])
    (letrec ([f (lambda (id logger)
                  (do
                      ((i 0 (+ i 1)))
                      ((= i 5))
                    (logger id))
                  (newline))])
      (f "logger1" logger-1)
      (f "logger2" logger-2))))

And the behaviour is exactly the same:

hoyte-closure.rkt> (logger-demo)
[logger1] Line number: 1
[logger1] Line number: 2
[logger1] Line number: 3
[logger1] Line number: 4
[logger1] Line number: 5

[logger2] Line number: 1
[logger2] Line number: 2
[logger2] Line number: 3
[logger2] Line number: 4
[logger2] Line number: 5

Racket is, in some ways, more elegant than even Common Lisp. I especially love the part where lambdas don’t need any funcallS or applyS to make them run (unlike in Common Lisp). Still, pretty much a branch off the same family tree.

Moving on, let’s try the same in Java, shall we?

import java.util.function.Function;

public class HoyteClosure {
    private static Function<String, Void> getLineLogger() {
        int lineNum = 0;

        return (String id) -> { lineNum++; System.out.printf("[%s] Line number: %d\n",
                                                                 id, lineNum); return null; };
    }

    private static void invokeLogger(String id, Function<String, Void> logger) {
        for (int i = 0; i < 5; i++) {
            logger.apply(id);
        }
        System.out.println();
    }

    public static void main(String[] args) {
        Function<String, Void> logger1 = getLineLogger();
        Function<String, Void> logger2 = getLineLogger();

        invokeLogger("logger1", logger1);
        invokeLogger("logger2", logger2);
    }
}

Okay, looks good. However, if we try to run it, we run into issues immediately:

Timmys-MacBook-Pro:Java8 z0ltan$ javac HoyteClosure.java 
Timmys-MacBook-Pro:Java8 z0ltan$ javac HoyteClosure.java 
HoyteClosure.java:7: error: local variables referenced from a lambda expression must be final or effectively final
        return (String id) -> { lineNum++; System.out.printf("[%s] Line number: %d\n",
                                ^
HoyteClosure.java:8: error: local variables referenced from a lambda expression must be final or effectively final
                                                                 id, lineNum); return null; };
                                                                     ^
2 errors

The problem is that Java really does not have real closures. The lambda support in Java 8 is just syntactic sugar for the good old anonymous class which can read local variables in the environment, but cannot modify them. So what can we do?

To make Java happy, we can create a new object for every logger instance i.e., use instance variables in lieu of local variables so that the modification of local variables is not an issue any more:

import java.util.function.Function;

public class HoyteClosureModified {
    static class Closure {
        private int lineNum;
        
        private  Function<String, Void> getLineLogger() {
            return (String id) -> { lineNum++; System.out.printf("[%s] Line number: %d\n",
                                                                 id, lineNum); return null; };
        }
    }

    private static void invokeLogger(String id, Function<String, Void> logger) {
        for (int i = 0; i < 5; i++) {
            logger.apply(id);
        }
        System.out.println();
    }

    public static void main(String[] args) {
        Function<String, Void> logger1 = new Closure().getLineLogger();
        Function<String, Void> logger2 = new Closure().getLineLogger();

        invokeLogger("logger1", logger1);
        invokeLogger("logger2", logger2);
    }
}

Taking it for a test spin, we get:

Timmys-MacBook-Pro:Java8 z0ltan$ javac HoyteClosureModified.java
Timmys-MacBook-Pro:Java8 z0ltan$ java -cp . HoyteClosureModified
[logger1] Line number: 1
[logger1] Line number: 2
[logger1] Line number: 3
[logger1] Line number: 4
[logger1] Line number: 5

[logger2] Line number: 1
[logger2] Line number: 2
[logger2] Line number: 3
[logger2] Line number: 4
[logger2] Line number: 5

It’s not the same though, is it? The whole point of using a closure was so that we wouldn’t have to do this explicit management of state ourselves. As such, Java doesn’t really have full-blown closures, just a poor man’
s version of it. Better luck next time, Java.

Finally, the same using Ruby. As I have said before, Ruby feels remarkably like a Lisp despite the syntactic differences.

module HoyteClosure 
    class Demo
        def self.get_line_logger
            line_no = 0

            lambda do |id|
                line_no += 1
                puts "[" + id + "] Line number: " + line_no.to_s
            end
        end

        def self.logger_demo(id, logger)
            5.times {
                logger.call(id)
            }
            puts ""
        end

        def self.main
            logger1 = get_line_logger
            logger2 = get_line_logger

            logger_demo("logger1", logger1)
            logger_demo("logger2", logger2)
        end
    end
end

And the final test run:

irb(main):009:0> load "./hoyte_closure.rb"
load "./hoyte_closure.rb"
=> true
irb(main):010:0> HoyteClosure::Demo.main
HoyteClosure::Demo.main
[logger1] Line number: 1
[logger1] Line number: 2
[logger1] Line number: 3
[logger1] Line number: 4
[logger1] Line number: 5

[logger2] Line number: 1
[logger2] Line number: 2
[logger2] Line number: 3
[logger2] Line number: 4
[logger2] Line number: 5

=> nil

Short, non-idiomatic, and sweet!