Archive for the 'J' Category

Image processing in J

2007-05-24

Some of my rough notes as I discover how I might go about doing some image processing in J.

This article mostly assumes you’ve been following my Learning J series: Part I, Part II, Part III, and Part IV.

Change working directory (cd) with «1!:44 ‘/Users/drj/project/fingerprint’». «!:» is the foreign conjunction.

Read file (as string): «t =. 1!:1 < ‘finger.pgm’» or a subset with «1!:11 ‘finger.pgm’;0 20».

The PGM file format is grayscale image format. It’s elegant simplicitly makes it ideal for prototyping image algorithms. It consists of a text header describing the width, height, and maxval (the value that represents maximum brightness, very commonly 255) followed by a big string of bytes (no compression, just the data in row major order).

Our first goal is to use J’s file mapping facilities which allow us to treat an array of bytes stored in a file as an array. For that we’ll need to find out the width, height, and maxval of the PGM file.

Regular expressions

require 'regex'
'(\S*\s+){3}(\S*\s)' rxmatch t

substrings can be extracted using the match results:

   ('P5\s+(\d*)\s+(\d*)\s+(\d*)\s' rxmatch t) rxfrom t
+-----------------+----+----+---+
|P5 3301 3397 255 |3301|3397|255|
+-----------------+----+----+---+

Observe that this duplicates t. That makes it candidate for a fork. Observe that the above expression has the form: «(x f y) g y». Recall that a fork «x (f g h) y» is the same as «(x f y) g (x h y)», so we can use a fork «’P5\s+(\d*)\s+(\d*)\s+(\d*)\s’ (rxmatch rxfrom h) t» if we can find a suitable h. We need a dyadic h such that «x h y» is y. Happily, «]» is such an h:

'P5\s+(\d*)\s+(\d*)\s+(\d*)\s' (rxmatch rxfrom ]) t

We can use «}.» to drop the first match (which describes the entire match, which I’m not really interested in):

'P5\s+(\d*)\s+(\d*)\s+(\d*)\s' (([: }. rxmatch) rxfrom ]) t

Notice the use of the cut «[:» and the extra set of parens.

Really we want to make a new monadic verb to extract the width, height, and maxval from a pgm file:

pgmxym =: ???

So we should bind the header regular expression onto rxmatch using the currying conjunction «&»:

pgmheader =: 'P5\s+(\d*)\s+(\d*)\s+(\d*)\s'
pgmxym =: ([: }. pgmheader & rxmatch) rxfrom ]

By placing the inner trident on the right we can eliminate a set of parens. We can do that by using the «~» (twiddles – has a terrible rendering on my browser/CSS) adverb (called passive in J) to swap the operands to rxfrom:

pgmxym =: ] rxfrom~ [: }. pgmheader&rxmatch

and now it’s this way round we can drop the initial «]» to give us a bident on the left. Observe that the monadic trident «[ g h» is the same as the monadic bident «g h». Note that if we wanted a bident anywhere else we’d have to use parentheses. So we now have:

pgmxym =: rxfrom~ [: }. pgmheader&rxmatch

I’m starting to feel like a proper J coder now.

Now we need to convert a boxed list of strings into 3 numbers.

«x “. y» converts y to a number, defaulting to x when that’s not possible. But before I discovered that I went on a merry excursion to implement equivalent functionality myself. Since the excursion does include some useful learning things about J it turned out not to be completely pointless, but is now relegated to an appendix.

In my excursion I did learn that «|.» is reverse, and dyadic «x i. y» is the index of y within x. And I rely on one of those facts shortly.

atoi =: 0&".    NB. much better than my version.

Mapped Files

require 'jmf' NB. J Mapped Files presumably
(JCHAR;width;headersize) map_jmf_ 'arrayname';datafn

I need to supply width, which is the width in bytes of each row, and headersize which is the initial amount of file to skip before the array proper begins. Now I need all the results from rxmatch; I need the total length of the header (which is essentially the first item of the rxmatch results) and I need the strings for the remaining 3 matches to be converted into numbers. I think that’s currently beyond my powers to do in a tacit definition. Explicit it is then:

pgmlxym =: verb define
m =. pgmheader&rxmatch y  NB. get matches
l =. 1{0{m                NB. Length of header
l , atoi @ > }. m rxfrom t
)

   'l w h m' =: pgmlxym t    NB. sets 4 variables

   (JCHAR;w;l) map_jmf_ 'fingerc';<'finger.pgm'

Cool. Now I have my image file as the array fingerc in J. There are two problems. The first is that it is an array of characters, not numbers; the second is that it’s huge and easy to accidentally print out as a J value (and being essentially binary data not edifying to print anyway). The first problem I can fix with: «finger =: a. i. fingerc» («a.» is alphabet, the list of characters in numerical order).

Simple operations can be performed. White–Black inversion: «f =. 255 – finger».

Now I have to figure out how to write a file out:

   fd =. 1!:21 'foo' NB. open file called foo.
   nf =. 0&":  NB. convert number to string in Natural Format.
   nf 127
127
   nf h
3397
   $nf h
4
   ('P5 ', (nf w), ' ', (nf h), ' 255 ') 1!:2 fd  NB. , forms list.
   g=. f { a.  NB. convert from character to number array.
   g 1!:3"0 1 0 fd  NB. append each row to file.
   1!:22 fd  NB. close file.

We can use some J’s provided facilities to produce simple plots of brightness.

load'misc'
nubcount ,/ finger

nubcount returns an N by 2 array where each item is entry, count. Where entry is one of the items of the operand to nubcount and count is the number of times it appeared. The list of unique items in a list is called its nub. The result array is an array of boxes because the counts are always numbers but the entries could be any type.

Do a nubcount and gather the nub into x and the corresponding counts into y:

x =. > 0{"1 count [ v =. > 1{"1 count [ count =. nubcount ,/ finger

Note the use of dyadic «[» which is really just being used to sequence 3 things on one line. The sequencing, of course, runs from right-to-left and this is a source of slight annoyance for me. I can sequence two things on seperate lines but when I want to put them on one line I can’t simply join the lines together with a «[» in between them. I have to swap the two lines round first.

It turns out that x does not have all the numbers from 0 to 255 (in other words its nub is not the same as «i. 256». This is because some values don’t appear in the input picture.

   x i. i. 256

gives us a list in order from 0 to 255 of where that entry appears in x or «#x» when it doesn’t appear. We can now get counts for all values from 0 to 255, by using this list to index v. Extending v with a single 0 means we correctly get a 0 count for values that don’t appear:

   (x i. i. 256) { v,0

and we can display this using plot:

plot (x i. i. 256) { v,0  NB. requires «require'plot'»
pd 'save bmp'  NB. saves to file ~/j601/temp/plot.bmp

Plot of brightness values and their counts.  Suspiciously wiggly.

Now in my case the plot is suspiciously wiggly. For a range of values the plot swings up and down wildly, as if the scanner (the original source) has some sort of quantisation artefact. For example, as it might appear if the bottom two bits were mysteriously returned as 0 1 most of the time.

I can recover some accuracy in the bottom 2 bits by rescaling the image. Since this requires me to actually remember some things from my degree I’ll do that later.

Appendix A – String to Number

Convert string to number:

   atoi =: [:(+10&*)/ [:|.'0123456789'&i.
   atoi '3155'
3155
   1+ atoi '3155'  NB. add one to prove that it's a number
3156

New things: «|.» is reverse, and dyadic «x i. y» is the index of y within x.

atoi uses cap, «[:», twice for the same reason: the trident «([: g h) y» is equivalent to «g h y» (we can’t use a bident because «(g h) y» is not «g h y», it’s «g y h y»). This is simple composition and can also be achieved with the «@» conjunction; «u@v y» is «u v y». Unfortunately conjunctions associate left-to-right (in so far as this is a reasonable way to think about it), so that «u @ v @ w» is «(u@v)@w». That means many more brackets in the form that uses «@»:

(+10&*)/@(|.@('0123456789'&i.))

The ability of cap to reduce parens is mentioned in its documentation.

So now we can glue everything together.

   pgmxym t
+----+----+---+
|3301|3397|255|
+----+----+---+

That’s a vector of boxes, each box containing a character array (string). Boxes are one of the atomic types that can appear as the 0-cells of an array. They’re just like pointers. They’re useful in this case because the answers, which are strings, are different lengths. We can’t have an array with rows of different length, so we can’t form an array directly from the strings ‘3301’, ‘3397’, ‘255’, because they’re not all the same length. So they’re boxed.

We can unbox with «>»:

   > pgmxym t
3301
3397
255

and then convert to a number:

   atoi > pgmxym t
332 335 95 180

Oh dear. We can see by comparing with the previous output that something has gone wrong with the rank of atoi. We could fix the rank with: «atoi”1 > pgmxyd t» but this still gives the wrong answers: 3301 3397 2560. The last result is wrong because atoi wasn’t applied to the string ‘256’ it was applied to the string ‘256 ‘ because when «>» produced its results they were an array so all the rows had to be the same length. Evidently atoi doesn’t work when there are non-digits in the string. The solution I chose was to compose atoi with «>»:

   atoi @ > pgmxyd t
3301 3397 255

Yay!

Learning J – Part IV

2007-05-12

Please see Learning J Part I, Part II, and Part III.

Strings of verbs that are not parseable with the usual dyadic–monadic machinery are called trains. (%+/) is a train of two verbs; the first verb is % (division), the second is +/ (the verb + modified by the adverb / to produce the sum-list verb).

A train of two verbs f g is called a hook (or bident, but that isn’t used as much). When used monadically (f g) x is the same as x f g x. Notice the repetition of the x operand.

   (+-)7  NB. 7 - 7 = 0
0
   (*-)2  NB. 2 * -2
_4
   (**:)3 NB. * is times and *: is square
27

So (%+/) n is the same as n % +/ n which if n is a list then this rescales the list so that the sum of the result is 1:

   i. 5
0 1 2 3 4
   (%+/)i.5
0 0.1 0.2 0.3 0.4

Dyadic hooks are boring, x (f g) y is the same as x f g y.

A 3-element train, f g h, is called a fork (or, again less often, trident). The monadic case (f g h) y is the same as (f y) g (h y), and the dyadic case x (f g h) y is the same as (x f y) g (x h y).

This is all tolerably well explained in Appendix F of the J dictionary.

The mnemonic that I use for remembering the difference between monadic and dyadic tridents is that the monadic case is just the same as the dyadic case but with x removed. Dyadic: (x f y) g (x h y); Monadic: (f y) g (h y).

Recall the parsing rules of Appendix E, and observe that larger sequences of verbs get decomposed into hooks and forks. b c d e is b (c d e); that is, the hook of b and the fork c d e. a b c d e is a fork of a fork: a b (c d e).

The classic pedagogical fork computes the average of a list:

   avg =: +/ % #
   avg 6 7 8
7
   avg 1 2 4 8 16
6.2
   avg 2 ^ i. 5
6.2

Observe that the repetition of operands is useful and can avoid temporaries. i.11 */ i.11 produces a multiplication table. We can use the fact that a bident duplicates its operand: (*/ g) i. 11 will do if we can find a monadic g that does nothing. Both [ and ] are monadic identities. So we can get the same multiplication table with (*/]) i. 11. As it happens this simple duplication is so useful that there’s an adverb, ~ (twiddles), to do it. u~ y is y u y. So */~ i. 11 also produces the same table.

Suppose we wanted to compute triangular numbers. tri(n) = (n×(n+1))/2. Perhaps we would like to use J to solve Gauss’s little school problem. Note that n×(n+1) can be computed with a bident: (*>:) (>: is the successor function). Now all we have to do is halve the answer. The currying conjunction & comes in handy. The monadic %&2 halves its operand; %&2 y is the same as y%2. We can use @ to compose these two:

   tri =: %&2 @ (*>:)
   tri i.10
0 1 3 6 10 15 21 28 36 45

In fact the brackets aren’t necessary. We can get rid of the brackets around the bident by using the monadic identity, [, in a trident:

tri =: %&2 @ [*>:

It’s a little shorter, but I’m not convinced that it’s any neater.

I tried this form, and it works, but not for the reasons that I thought it did. The spacing I’ve used above suggests I have a trident on the right, a curried divide operator on the left, and I’ve joined them with @. We can use J to see how it’s actually been parsed:

   %&2 @ [*>:
+-------------+-+--+
|+-------+-+-+|*|>:|
||+-+-+-+|@|[|| |  |
|||%|&|2|| | || |  |
||+-+-+-+| | || |  |
|+-------+-+-+| |  |
+-------------+-+--+

The kinda scary looking boxes are just another way to write brackets (in this case). So %&2 @ [*>: turns out to be parsed as ((%&2)@[)*>:. Lesson: be careful. This is actually computing (n/2)×(n+1); of course this is mathematically the same as (n×(n+1))/2 but the latter can be done in integer arithmetic whereas the former requires fractions. Good job halving is an exact operation in IEEE arithmetic.

The reason %&2@[*>: gets parsed as it does is that the trident reduction cannot take place if there is a conjunction to the left of the potential trident. When the stack has the four terms @ [ * >: on it, @ is a conjunction so [ * >: will not be reduced to a trident. The conjunctions get reduced first.

Conjunctions get reduced left to right. %&2@[ is (%&2)@[. Referring to the parsing table again we see that’s because a conjunction won’t be reduced if there is a conjunction immediately to its left.

Since [ is monadic identity, the [ in %&2@[ is not necessary. We can just use %&2 instead: %&2*>:. It also turns out that dividing by 2 is sufficiently useful that there’s a primitive to do it: -:. So we can use tri =: -:*>:, which is just a single trident.

Cap, spelt [:, is a magic verb used in tridents. [: g h is the same as f g h but without the entire f branch. So x ([: g h) y is g (x h y), and ([: g h) y is g h y.

The last form of cap is found in our original triangle formula that used @: tri =: %&2 @ (*>:). We can remove the @ conjunction and replace it with a cap instead:

   tri =. [: %&2 (*>:)

And this time we can replace the bracketed bident on the right with a trident that uses [:

   tri =. [: %&2 [*>:
   tri
+--+-------+--------+
|[:|+-+-+-+|+-+-+--+|
|  ||%|&|2|||[|*|>:||
|  |+-+-+-+|+-+-+--+|
+--+-------+--------+

This does get parsed how we (or at least I) expect, with [ * >: on the right being reduced to a trident.

Using -: and, for amusement, swapping ] for [ we get:

   tri =: [:-:]*>:

To be honest this seems like an exercise in fruitless manipulation, but I’m sure I’ll be finding all sorts of witty things we can do with forks and hooks.

Learning J – Part III

2007-04-27

Please see Learning J Part I and Part II.

Syntax

At the lexical level J is fairly unsurprising. A program consists of a series of sentences, one sentence per line (I think we can already see how the issue of breaking long lines never comes up). Comments are introduced with NB. and finish at the end of the line. Sentences are decomposed into words.

Examples words:

blue
blue_green
7
_7
-
=:
'foo'
i.
$
"
\\
[:

Names and numbers are pretty standard (but note that negative numbers are denoted using _, like ML, because - is a verb), but apart from those there is a bewildering array of punctuation available including items that are usually found as brackets, delimiters, and escapes in other languages.

There’s an additional quirk. A sequence of numbers separated by spaces forms a single word (a list). This only works for numbers. So 3 1 2 is a single word (a length 3 list), but a b c is not.

Each word is categorised into a part of speech. J deliberately uses terminology from natural language grammar.

  • Nouns: values to you and me. 1, 2 3 4, 'foo', and so on.
  • Verbs: functions or procedures. +, $, i..
  • Adverbs: monadic higher order functions. /, \.
  • Conjunctions: dyadic higher order functions. ", and perhaps lots more.
  • Punctuation: ( and ) (which have their conventional meaning) and maybe some more.
  • Copula: What J calls =: and =. for assigning names to things.

As we’ve seen, verbs can either be monadic or dyadic, so that’s: term verb term or verb term. I’m being deliberately vague about what a term is (mostly because I don’t know).

Adverbs are always monadic and follow the verb: term adverb.

Conjunctions are always dyadic: term conjunction term.

Let c be a conjunction, v be a verb, and a be an adverb.

There’s an obvious x v y v z ambiguity, as in 2^3^4. As previously discussed things group to the right, so this is 2^(3^4):

   2^3^4  NB. some number much larger than 256 ((2^3)^4)
2.41785e24

Conjunction Adverb Precedence

What about v c v a? Is that (v c v) a or v c (v a)?

Let’s find out. Consider *: @ + / 1 2 3. There’s two new symbols I need to explain. Monadic *: is square (it squares its argument). @ is a conjunction called Atop, it’s a kind of compose operator.

So *: @ +/ 1 2 3 could mean either (*: @ +) / 1 2 3 which would fold the dyadic (*: @ +) over the list 1 2 3 or it could mean *: @ (+/) 1 2 3 which would apply the monadic *: @ (+/) to the list 1 2 3. (It could also mean *: @ (+/ 1 2 3), but it doesn’t.) The @ conjuction is defined so that when used dyadically (as in the first possible interpretation) x (*: @ +) y means the same as *: (x + y) (square the sum); when used monadically *: @ (+/) y means the same as *: (+/) y.

So the first interpretation would have the meaning 1 (*:@+) 2 (*:@+) 3 which is 676 (262). The second interpretation would have the meaning *: (+/ 1 2 3) which is 36. Let’s see:

   *:@(+/) 1 2 3
36
   (*:@+)/ 1 2 3
676
   *:@+/ 1 2 3  NB. Same as second example.
676

So we can see that the @ conjunction binds more tightly than the / adverb. Conjunctions have higher precedence.

Operator precedence is not enough

Sadly, whilst it’s tempting to think that you can parse J using an operator precedence parser, you can’t. That’s because the reductions to apply depend not on the syntactic category of the items being parsed but on their runtime class.

Consider what might happen if you had a conjunction whose result was sometimes a verb and sometimes a noun. This is extremely unconventional, but possible. I introduce the notion here to show how certain methods of parsing are not possible. I borrow from the future and show you my evil conjunction:

   ec =: conjunction define
if. n = m do. *: else. 4 end.
)

The evil conjunction ec takes two (noun) arguments and has the result *: (which is a verb) if they are equal, and the result 4 (which is a noun) if not. Now consider n ec m - 3. Is this ((n ec m)(- 3)) (monadic verb applied to - 3) or ((n ec m) - 3) (dyadic - applied to two nouns)? Actually it could be either:

   7 ec 0 - 3    NB. 7 ec 0 evaluates to the noun 4
1
   7 ec 7 - 3    NB. 7 ec 7 evaluates to the verb *: (square)
9

So the parsing of J is mingled with its execution. The way it actually works is that the sentence forms a queue of words. Words are moved from the right-hand end of the queue onto a stack. After every move the top four elements of the stack are considered and one of 9 possible reductions is applied. When no more reductions are possible another word is moved across to the top of the stack and the cycle repeats. This is all reasonably well described by the J dictionary appendix E.

It strikes me as a mix of elegant simplicity, stomach churning madness, and pragmatic considerations of actually implementing something on 1950’s hardware.

Next, part IV covers more syntax (trains) and introduces some more practical examples of conjunctions.

Learning J – Part II

2007-04-11

See Part I for essential background on arrays.

The sub-arrays of an array of rank N are called cells. A k-cell is an array of rank k that is part of a (usually) larger dimensional array. An N-dimensional array can be simultaneously regarded as being an N-dimensional array of 0-cells (atoms), an N-1-dimensional array of 1-cells, an N-2-dimensional array of 2-cells, and so on. Thus a 2 x 3 x 4 array can be regarded as a 2 x 3 x 4 array of 0-cells (scalars), a 2 x 3 array of 1-cells (each of which is a length 4 vector in this case), a length 2 vector of 2-cells, or the entire array can be regarded as a 3-cell. The cell is defined to be something sensible even when k > N, namely the whole array.

The shape of the k-cells of an array is the rightmost k items of the shape of the array.

The k-frame of an array is the leftmost part of the array’s shape when the shape of the k-cells is taken away.

When k is N-1 then the array is considered as a vector. In this case the k-cells are called the items of the array.

This rank of a verb governs what cells of a noun the verb applies to. A verb of rank r maps over all the r-cells of a noun. The result is an array of the shape noun’s r-frame. The result is an array of whatever the result of applying the verb to each r-cell is.

The k-cell terminology is useful in explaining the behaviour of J programs. It is also useful when we change the rank of a verb.

The monadic verb i. produces a 0-based sequence of integers in the shape of its (right) operand. i. 3 ⇒ 0 1 2. It works with higher ranks too:

   i. 2 3 4
 0  1  2  3
 4  5  6  7
 8  9 10 11

12 13 14 15
16 17 18 19
20 21 22 23

The monadic verb {. returns the first item of its (right) operand; it’s called head for this reason. Ordinarily {. has rank infinity, denoted in J by _, meaning it gets applied to the entirety of its operand:

   {. 9 1 1  NB. simple use of {.
9
   i. 2 3  NB. an array of shape 2 3
0 1 2
3 4 5
   {. i. 2 3  NB. returns first item of the array, which is a vector of length 3
0 1 2

We can make {. apply to cells of a smaller rank by using the " conjunction. {."k makes a new verb that is like {. but has rank k. So if we apply {."1 to i. 2 3 (shape 2 3) the result will have a shape of the 1-frame of i. 2 3, that is, shape 2. The contents will be the heads of the 1-cells of i. 2 3:

   {."1 i. 2 3
0 3

Next up: syntax.

Learning J – Part I

2007-04-09

The preferred way to learn J seems to be via a series of half-truths and tutorials. I hate learning like that. I want The Truth. (Since I originally wrote that I’ve discovered the cryptic documentation for J. Life is good.)

The basic types in J are the number and the array. There are other types too, like character, and I suspect more that I don’t know about. I expect verbs and adverbs (functions and higher-order functions) will turn out to be members of some type. Values are called nouns.

The array appears more fundamental in the sense that every other noun exists as an element in some array (I think). Like Lisp an array has N dimensions or axes. The number of axes, N, is called the rank. N >= 0.

An array of rank 0 contains one value. An array of rank 0 is called an atom or scalar. Compare this to #0A7 in Lisp (bet that has you looking up reader syntax).

Each axis has a non-negative length and is indexed using a 0-based index.

Arrays of rank 1 are called vectors and also lists. They have a convenient literal syntax:

1 2 3 NB. vector of length 3

Aside: comments are introduced with «NB.»; this is kind of cool and kind of perverse.

Computation is performed by applying verbs to nouns. Various verbs have a literal syntax; verbs can also be produced from adverbs. A given name, such as $, can stand for a monadic verb (1-ary) or dyadic verb (2-ary) according to how it is used. Syntax for monadic application is verb noun, for dyadic application is noun verb noun. Adverbs come after the verb: verb adverb. Evaluation and grouping is generally right to left. So 2 * 3 + 4 evaluates to 14 (dyadic * and + have the conventional meaning).

Monadic $ returns the shape of an array, which is a vector of its dimensions (like Lisp’s array-dimensions). Monadic # returns the length of a vector (like Lisp’s length).

In the following example my typing is indented, the results printed out by J are exdented. This is conventional for J.

   $ 1 2 3
3
   # 1 2 3
3
   $ 9 NB. Result is a 0-length vector.  Which prints as a blank line:

Note the last result. $ applied to the scalar 9 (an array of rank 0) yields a vector of length 0.

Applying # to the result of $ will give us the rank:

   # $ 1 2 3
1
   # $ 9
0

Dyadic $ can be used to construct arrays of arbitary shape (left argument) filled in with some value (right argument):

   2 3 $ 1
1 1 1
1 1 1
   2 0 3 $ 9    NB. an axis is 0, hence 0 elements
   # $ 2 0 3 $ 9
3

Note that the second array in this example has a zero-sized axis. It contains no values but still retains its shape. This is very similar to the situation in Lisp: (array-dimensions (make-array ‘(2 0 3))) ⇒ (2 0 3).

Strings have a literal syntax, ‘foo’, and are vectors. Except—hack!—a literal string with just one character is a scalar:

   'foo'
foo
   $'foo'
3
   $''
0
   $'f' NB. Recall a scalar's shape is a 0-length vector.

Dyadic $ can take a vector on the right (and arrays of higher rank, but something slightly hairy happens then):

   2 3 4 $ 'foo'
foof
oofo
ofoo

foof
oofo
ofoo

Observe how ‘foo’ is used to fill in the array, how the rank 3 array is displayed, and how the elements are ordered lexicographically by index (row major, but that gets slightly confusing above rank 2).

The adverb / is what we know and love as foldr (if only every higher order function had its own domain name). / turns a dyadic verb into a monadic verb that folds the dyadic verb along a list (“inserts into” according the J crowd). It can be used to yield the number of atoms in an array:

   2 * 3
6
   */ 2 3
6
   */ 2 3 4
24
   */ $ 2 2 5 $ 'foo'    NB. same as */ ($ (2 2 5 $ 'foo'))
20
   */ $ 7
1

Note the last example, the scalar’s shape ($ 7) is a 0-length vector which when * is folded over it yields 1. 1 is the identity for *. Recall that in Lisp (*) ⇒ 1 for similar reasons.

There’s plenty more to learn about arrays, and that’ll come in part II.

PS. If J intrigues then see how I learnt to multiply in colour using it.

Learning my multiplication tables in J—again

2007-04-05

I like learning new programming languages. It’s like a whole new way of thinking. I thought I’d have another look at J (an ASCII descendent of APL). APL and J clearly enshrine a way of thinking that is unusual amongst programming languages, and that alone makes them worth learning. I last looked at J about 10 years ago. My head exploded. This time the tutorials seem to have a tiny bit more explanation to them.

I learnt something that I wasn’t expecting (invaluable). I learnt that if you take two single digit numbers and multiple them and take the last digit of the answer, then you get the same last digit if you subtract each of the starting number from 10 and do the same thing. 3 × 4 = 12; 7 × 6 = 42. Note that 7 is 3 from 10 and 6 is 4 from 10; we could say that 7 and 6 were the complements in 10 of 3 and 4.

Learning this new thing happened as I was bashing away at the J prompt. One of the examples that comes with J produces an addition table with code like this: (i.5) +/ (i.5). And you can produce a coloured quilt pattern with viewmat (i.5) +/ (i.5) (or at least you can once you’ve remembered to type «require ‘graph’» first):

plus4.png

So I thought that a multiplication table mod 10 would be a good idea. It shows the last digit of a multiplication. The code for that is easy: viewmat 10 | (i.11) */ (i.11):

times10.png

The first thing I noticed was that there was a reflection symmetry along the main-diagonal. That’s easy to explain, multiplication is commutative so x × y = y × x.

The next thing I noticed suprised me. There was a reflection symmetry along the other diagonal (the counter-diagonal). I wasn’t expecting that at all. I thought about this for a bit. So what I seem to be seeing is that:

a ⊗ b = (10 – a) ⊗ (10 – b)

where ⊗ denotes multiplication in the ring of integers modulo 10. Well that’s easy to see with a bit of algebra:

(10 – a) ⊗ (10 – b) = (-a) ⊗ (-b) = a ⊗ b

or without using a ring:

(10 – a) × (10 – b) | 10 = 100 – 10×a – 10×b + a×b | 10

by multiplying out; and we can see that 100 and 10×a and 10×b are all 0 | 10, so the right hand side reduces to:

a×b | 10

Another way of thinking about this is that adding 10 to a number obviously isn’t going to affect the last digit of a multiplication. Nor is taking away 10. So subtracting a number from 10 is just like negating it; and negating both numbers obviously doesn’t change the answer when you multiply them together. We can see this repeating pattern in J with viewmat 10 | (i:10) */ (i:10) which gives the table for integers from -10 to 10:

timesm10.png

Aside: I find the above image a bit disturbing to look at. Some part of my brain wants to believe that it has left-right and top-bottom mirror symmetry (which it almost does have) and is fighting with the bit of brain that can see that it doesn’t have mirror symmetry.

A larger repeating version can be seen with the code viewmat 10 | (i:40) */ (i:40):

timesm40.png

Further aside: I produced these pictures by saving them as BMP files using savemat_jviewmat_ in J and converting them to much smaller PNG format using the excellent netpbm suite. In the BMP files all the blues got swopped for reds and vice-versa. Someone got confused as to whether the colours were specified RGB or BGR, so I had to channel swop them back again. Of course that’s pretty easy to do using netpbm. Bottom line: BMP sucks.

So the thing that impresses me about J was that I was just playing around with it casually and discovered for myself this little fact about numbers that I hadn’t known before. This is how it should be when we’re using a tool for learning. It reminds me of the way you can discover things about geometry by playing around with Logo. It makes me want to use computers as an exploratory tool for teaching children maths through discovery.

J itself still makes me think my head is about to explode.

If J intrigues you from this taste, perhaps you ought follow along with me: Learning J part I.