kivikakk.ee

Not-so-phantom types

Back before I had a clue what I was doing with OCaml, I read an article on Jane Street Capital’s OCaml blog about using phantom types for static access control—read: totally awesome. I stumbled across a situation that lead me to wonder if I could apply part of that knowledge here.

The short answer is: you can. What am I using it for? Storing the saved status of a record (namely, whether or not it has an id/given primary key associated with it) as a phantom type. I also use the type used for attaching the phantom types to store the primary key itself, which has an associated overhead (and makes the attachee type decidedly not phantom).

The relevant code follows. In my case, the primary keys are of type int32, so they’re what’s buried in the type.

(* pK.ml *)
type none
type some

type ('con,'a) t = int32 option * 'a

let none t = (None,t)
let some k t = (Some k,t)
let get = snd

let pk t = Option.get (fst t)
(* equiv to: match fst t with | Some n -> n | None -> raise Option.No_value *)

let pk_opt = fst

So far, this looks like a pretty standard way to attach a given piece of data to any other piece of data, except for those strange, phantom (not abstract, because there’s no underlying definition) types at the top which never seem to be used, and the similarly unused 'con type variable on t.

The magic happens, of course, in the .mli:

(* pK.mli *)
type none
type some

type ('con,'a) t

val none : 'a -> (none,'a) t
val some : int32 -> 'a -> (some,'a) t
val get : ('con,'a) t -> 'a
val pk : (some,'a) t -> int32
val pk_opt : ('con,'a) t -> int32 option

So, as we recall, the definition of none is let none t = (None,t). The right-hand side matches the definition of t faithfully, as it’s a int32 option * 'a, but we’ve also filled in the 'con type variable, by saying its type is none.

At compile-time, this gets optimised away, because there is no value for the none type. But during compile-time, the type is known.

some is defined as let some k t = (Some k,t), so we know the value k is being stored safely in the int32 option. But the 'con type variable is also specified as some.

Let’s skip ahead and look at pk. It takes a (some,'a) t and yields an int32. That means that, for example, PK.pk (PK.none 42) doesn’t typecheck:

Error: This expression has type (PK.none, int) PK.t
       but an expression was expected of type (PK.some, 'a) PK.t

If we omitted the .mli file, we’d get an exception at run-time instead.

It’s important to remember that this technique has nothing to do with the actual bundling of data and subsequent hiding—that’s a perfectly normal thing to do. The benefit here is in making certain assertions about whether or not that data is actually present; we can be sure that PK.pk will never throw an exception, because the object passed to it could only have been created by PK.some.

Note that we do experience some some additional runtime slowness due to the use of an int32 option (and subsequently Option.get or matching on that to retrieve its value). If you’re happy to sacrifice PK.pk_opt, you can do something like this instead:

(* pK.ml *)
type none
type some

type ('con,'a) t = int32 * 'a

let none t = (0l,t)
let some k t = (k,t)
let get = snd
let pk = fst

The .mli is the same, except with pk_opt removed.

This is much more concise, as the boolean status of “is the primary key present?” is not stored at all at runtime. The upshot is that you also have no way to tell at runtime. This isn’t a “problem” in and of itself, because the type-checking means you’ll never accidentally see the 0l value stored with the none type (we just need to put something there, without an option type)—but it means that there’s no way to do anything at runtime that differentiates between the two.

If you don’t need to, then this is great, too, because it’s exactly how you can achieve the static access control, as described in Yaron Minsky’s post referred above—you can also attach additional data if you want to drag information along with the typing data!

So, how am I using this? Here’s an example interface for a record type which has an associated database table:

(* world.mli *)
type base_t = { name: string;
                width: int; height: int;
                defaultTileId: int32;
                placements: placement_t array }
           
type 'con t = ('con,base_t) PK.t

val empty : PK.none t

val of_id : int32 -> PK.some t
val save : 'con t -> PK.some t

We can ignore the details of this—the base type, 'con t, will either have PK.none or PK.some filled in for 'con.

As an example, there’s a default “empty” record, empty. In the .ml, it’s defined like so:

let empty = PK.none { name="";
                      width=0; height=0;
                      defaultTileId=0l;
                      placements=[||] }

This means that we can’t accidentally treat this as a record that actually has a corresponding row in the database. This has already caught a bug in my application—as soon as I implemented this, the type-checker alerted me where I was allowing users to belong in unsaved worlds, which would cause a problem as soon as I tried to save the user out to the database (and serialise the database ID as zero).

There’s also a certain elegance in the type statement val save : 'con t -> PK.some t, in my opinion.

Curry of evil

I had an amusing thought in bed last night, and I was fortunate enough to remember it:

What if currying wasn’t all good?

# let f x =
    let now = CalendarLib.Time.now ()
    in
    fun y ->
      if CalendarLib.Time.now () <> now then
        x - y (* !! *)
      else
        x + y;;
val f : int -> int -> int = <fun>
#

The type-signature is sure innocuous.

Hence:

# f 1 2;;
- : int = 3
# f 100 ~-123;;
- : int = -23
# let add100 = f 100;;
val add100 : int -> int = <fun>
# add100 77;;
- : int = 23
# (* !! *)

I don’t know what convinced me to do this, but I was thinking along the lines of, “OCaml makes all functions curryable, so someone seeing a type-signature of int -> int -> int is so used to thinking of it as a (curryable) function that “takes two arguments”, that they might forget that real things could happen between “fixing” arguments one and two.”

This demonstration is somewhat poor (relying on CalendarLib.Time), but it still gives me pause for thought.

After many discussions recently at work with my coworker who does our webdev and DBA about how crap MySQL is, I decided to finally check out the alternative which I’ve known since the start was better (yet never have bothered [dared?] to try): PostgreSQL.

A brief overview of PostgreSQL

Postgres is a generally better polished piece of software (often compared to , with less rubbish surrounding its licensing (fuck you, MySQL AB Oracle), better extensibility (PL/*), better standards compliance, foreign-key constraints (which are often forced in software instead in MySQL), a much richer type set .. sold you yet? You can have frickin’ multi-dimensional arrays as column types, and query on subelements! Amazing.

Of course, if you install the postgresql and postgresql-client packages, you’ll find you have an installation which you can do very little with. (no way to get in by invoking psql).

Postgres does its authentication—by default—a bit differently. After installing the server, you’ll have a new postgres user on your system; if you su into it (perhaps via a superuser account), you’ll now be the superuser for your database server, too, by virtue of being logged into that account. Postgres—again, by default—ties the database accounts to the system ones.

We can now use createuser to make an account for our regular user. Since I’m doing this on a development machine (my laptop), I’ll just create a superuser account for it. My account’s called “celtic”, so it’s just a matter of entering createuser -s celtic. Read createuser’s man page for more.

Exiting out of those subshells and back as our regular user, we now can create ourselves a database to toy with, using createdb. All Postgres tools that operate on databases will default to using your username as a database name (i.e. celtic’s default database is named celtic). createdb is no different, so you can just invoke it with no arguments and it’ll make your default database after a short delay.

You can now invoke psql, and get a lovely prompt:

(celtic) ~:6320 (0)% psql
psql (8.4.5)
Type "help" for help.

celtic=#

The word celtic at the prompt represents the database I’m using, and the # is because I’m a superuser (non-superusers see >).

Now that we can connect to our database and mess around with stuff, let’s take a look at the SQL understood by Postgres.

It differs in small ways from MySQL. Table and column names lose their capitalisation if you don’t quote them, for example:

celtic=# create table XYZabc ();
CREATE TABLE
celtic=# \d
        List of relations
 Schema |  Name  | Type  | Owner  
--------+--------+-------+--------
 public | xyzabc | table | celtic
(1 row)

celtic=# create table "XYZabc" ();
CREATE TABLE
celtic=# \d
        List of relations
 Schema |  Name  | Type  | Owner  
--------+--------+-------+--------
 public | XYZabc | table | celtic
 public | xyzabc | table | celtic
(2 rows)

celtic=#

Quoting is another good point. Backticks aren’t used for identifiers; instead, use double-quotes (!). Single-quotes quote strings. This may take a moment to get used to.

Another thing is Postgres’s explicit use of sequences. In MySQL, if you want a unique numeric ID for a table, you’d probably just add a column like abcId INT PRIMARY KEY NOT NULL AUTO_INCREMENT, with a few caveats: there can be only one AUTO_INCREMENT per table, it must be indexed, they don’t work if you try to use negative numbers with them, and it has to be an integer or floating point number column.

Postgres has a construct that looks quite similar; abcId SERIAL PRIMARY KEY NOT NULL. In this case, SERIAL is the “type” of this column, but what it ends up looking like is quite different:

celtic=# create table abc (abcID serial primary key not null);
NOTICE:  CREATE TABLE will create implicit sequence "abc_abcid_seq"
for serial column "abc.abcid"
NOTICE:  CREATE TABLE / PRIMARY KEY will create implicit index
"abc_pkey" for table "abc"
CREATE TABLE
celtic=# \d
             List of relations
 Schema |     Name      |   Type   | Owner  
--------+---------------+----------+--------
 public | abc           | table    | celtic
 public | abc_abcid_seq | sequence | celtic
(2 rows)

celtic=# \d abc
                           Table "public.abc"
 Column |  Type   |                      Modifiers                      
--------+---------+-----------------------------------------------------
 abcid  | integer | not null default nextval('abc_abcid_seq'::regclass)
Indexes:
    "abc_pkey" PRIMARY KEY, btree (abcid)

celtic=# \d abc_abcid_seq
        Sequence "public.abc_abcid_seq"
    Column     |  Type   |        Value        
---------------+---------+---------------------
 sequence_name | name    | abc_abcid_seq
 last_value    | bigint  | 1
 start_value   | bigint  | 1
 increment_by  | bigint  | 1
 max_value     | bigint  | 9223372036854775807
 min_value     | bigint  | 1
 cache_value   | bigint  | 1
 log_cnt       | bigint  | 1
 is_cycled     | boolean | f
 is_called     | boolean | f

celtic=#

That’s a lot to digest!

When we create the table, PgSQL tells us it’s creating an implicit sequence called abc_abcid_seq for the serial column abc.abcid. Okay. The PRIMARY KEY invocation is also expanded into creation of an index; note that Postgres tells you these things explicitly. This is also a nice reminder that these things can be done manually, too.

When we detail the database with \d, we now see there are two relations; our table, and its sequence. Note that the sequence isn’t really explicitly bound to the table in any way, it’s just named so you can tell it belongs to it.

Inspecting the table, we can see that abcid is now actually an integer column marked not null. It also has a default value, nextval('abc_abcid_seq'::regclass). This is actually a function call—Postgres supports arbitrary expressions (subject to some caveats) for calculating default values, not just NOW().

I won’t delve into the function call too much at this stage, but nextval() is an Postgres-supplied function which takes a handle to a relation (which should be a sequence), which is of type regclass, and returns the next value the sequence should generate, as well as causing it to advance its internal pointer such that it’ll return the following number next time.

The paamayim nekudotayim :: is the cast operator, and in this case casts the string-literal 'abc_abcid_seq' to a regclass. Technically it’s not necessary, as it gets casted implicitly for you anyway:

celtic=# select nextval('abc_abcid_seq');
 nextval
---------
       1
(1 row)

celtic=# select nextval('abc_abcid_seq');
 nextval
---------
       2
(1 row)

celtic=#

.. but I suppose the system is being explicit, given that it’s the one generating the values.

So that’s how the serial column “type” works in Postgres. You can use these for anything, and not necessarily tied to only one table, or any table at all; perhaps you create a standalone sequence (CREATE SEQUENCE xyzzy), then use it in some functions. There’s a family of functions for manipulating its value manually, so you have complete control of how the sequence is generated. It’s a really neat mechanism, and I’m looking forward to exploiting it in my own applications.

Enter PG’OCaml

Now, let’s say we wanted to use this amazing database system in our very own OCaml application. The first thing I did was look for a Debian package called libpostgresql-ocaml-dev, and lo and behold, there’s one! I installed it, and searching for docs for it, I stumbled upon the homepage of PG’OCaml. Normally I eschew the “non-standard” library, but I was pleasantly surprised to find that this was also in Debian: libpgocaml-ocaml-dev! Let’s install that instead.

Its killer feature? PG’OCaml type-checks your SQL statements at compile-time to make a strong, type-safe SQL library with syntax extensions so you do no manual (and unsafe) casting of data, nor do you accidentally pass the wrong type of data when trying to concatenate a barely-injection-safe query together.

The “downside” (if you can call it that) is that PG’OCaml needs access to your database at compile-time to find out the structure of your database. This is rarely an issue. The amazing thing is that, not only does it make sure that you’re working with the right types and doing all the ugly conversion under-the-table for you, it also carries the amazing feeling of using a safe static-type-inferring language right through to your database layer: make a change to your database (that mangles your code without you realising), and you’ll now get a compile-error when you recompile! Of course, the caveat is that you have to recompile to get the knowledge upfront, but you’ll get runtime errors as well, just like you would with any other database connector.

Let’s begin coding with PG’OCaml:

let report (name,age) =
  Printf.printf "%s is %d years old\n%!" name age

let dbh = PGOCaml.connect ()
in
let results =
  PGSQL (dbh) "select name, age from tblpeople"
in
List.iter report results

This is deceptively simple: we connect to a database (where are the connection settings?!), query it using PGSQL, and then List.iter on the supposedly well-formed and well-typed result?!

The answer, of course, is yes.

To get this running, try compiling it using ocamlfind with a line like this:

ocamlfind ocamlc -linkpkg -package pgocaml.syntax -syntax camlp4o test.ml -o test

Bam! Compile error:

ERROR: 42P01: relation "tblpeople" does not exist
File "test.ml", line 7, characters 2-47:
Camlp4: Uncaught exception: PGOCaml_generic.Make(Thread).PostgreSQL_Error ("ERROR: 42P01: relation \"tblpeople\" does not exist", [(83 | CstTag84, "ERROR"); (67 | CstTag68, "42P01"); (77 | CstTag78, "relation \"tblpeople\" does not exist"); (80 | CstTag81, "23"); (70 | CstTag71, "parse_relation.c"); (76 | CstTag77, "885"); (82 | CstTag83, "parserOpenTable")])

File "test.ml", line 1, characters 0-1:
Error: Preprocessor error

There’s a lengthy error courtesy of camlp4, but the first line is the important one; the table doesn’t exist! We’re informed at compile-time. Saviour!

Let’s fix this in psql:

celtic=# create table tblpeople (name varchar primary key not null, age int not null);
NOTICE:  CREATE TABLE / PRIMARY KEY will create implicit index "tblpeople_pkey" for table "tblpeople"
CREATE TABLE
celtic=# insert into tblpeople values ('Mysterious', 21), ('Anneli', 20), ('Bjoerk', 45);
INSERT 0 3
celtic=#

Compiling again gives us a slightly different error:

File "test.ml", line 9, characters 17-24:
Error: This expression has type
         (string * int32) list PGOCaml.monad PGOCaml.monad =
           (string * int32) list
       but an expression was expected of type (string * int) list

Well, you can’t get everything right the first time. We defined tblpeople.age as an int in Postgres, which is 4 bytes long. An OCaml int, on the other hand, is either 31 or 63 bits long (depending on your machine architecture) due to their tagged pointer representation, and PG’OCaml will not sacrifice the accuracy silently.

Since we’re not concerned about the last bit (we hope no one should live that long ..), just fix the report function:

let report (name,age) =
  Printf.printf "%s is %d years old\n%!" name (Int32.to_int age)

(Edit: as Eric pointed out in the comments, an easier way is to just print the int32 itself using %ld in the format string!)

Recompiling gives great success. Now run:

(celtic) pgo:6427 (0)% ./test
Mysterious is 21 years old
Anneli is 20 years old
Bjoerk is 45 years old
(celtic) pgo:6428 (0)%

Just like that, it works! The types were all inferred, the database connection was smooth.. it all just worked.

PG’OCaml details

Connection strings, connection options

PG’OCaml looks to your environment to determine which database to use, both when compiling and running. The environment variables are the same used by the Postgres tools themselves, so this is a great help: set PGDATABASE, PGHOST, PGHOST, etc. if need be.

You can also override options manually in the code itself, and they’re specified separately (and possibly extraneously) for the compile-time stage, and run-time.

For compile-time, you can set options by using connection strings just before a query itself:

let results =
  PGSQL (dbh) "database=mydb" "user=jenkins" "select name, age from tblpeople"

These are honoured at compile-time when type-checking (and type-determining, I suppose) each individual PG’OCaml expression, and override environment variable settings.

These are not to be found at run-time—indeed, the information is relevant and necessary only once at runtime: when connecting. For that reason, the PGOCaml.connect function has this type-signature:

val connect : ?host:string ->
       ?port:int ->
       ?user:string ->
       ?password:string ->
       ?database:string ->
       ?unix_domain_socket_dir:string ->
       unit ->
       'a t monad

Thus, to have the program use the same (forced) connection settings at runtime:

let dbh = PGOCaml.connect ~user:"jenkins" ~database:"mydb" ()

There’s obviously an advantage to these being separate, as it means computed/inputted values can be used for the connection at runtime (i.e. in production), a concept which makes little sense at compile-time. I tend to use environment variables to control the compile-time settings.

PGOCaml

The module name in OCaml is PGOCaml, not PGOcaml. This tripped me up.

Parameterised fields

They’re easy! (surprise!) Let’s say you have a value (id : int) which you want to match on an integer column in the database:

let result =
  PGSQL (dbh) "SELECT data FROM tblentities WHERE entityid=$id"

It’s that simple! Right? Wrong! OCaml’s int and Postgres’s integer don’t mix! Simply fixed, however:

let pid = Int32.of_int id
in
let result =
  PGSQL (dbh) "SELECT data FROM tblentities WHERE entityid=$pid"

It’s even better, though, if you just agree to use int32s elsewhere, though!

The exact same syntax works for INSERTs, too. There’s also a nifty feature: use $?name instead of $name, and it’ll type as an option type—Some x will become x (converted appropriately), but None will render as NULL. Nifty!

For more reading on PG’OCaml

See the PG’OCaml website, and this informative tutorial by Dario Teixeira. I strongly suggest you read both, as there’s a lot more to both PostgreSQL and PG’OCaml.

My first Monad

I’ve finally made my first monad; I’m still not 100% sure if I’ve really come to grips on it entirely. Here’s its definition:

import System.IO
import Control.Applicative

newtype IODirector a = IODirector { runIODirector :: (Handle,Handle) -> IO (a, (Handle,Handle)) }

instance Monad IODirector where
  return a = IODirector $ \hs -> return (a, hs)
  m >>= k  = IODirector $ \hs -> do (a, hs) <- runIODirector m hs
                                    runIODirector (k a) hs

class MonadDirectedIO a where
  dPutStr :: String -> a ()
  dPutStrLn :: String -> a ()

  dGetLine :: a String
  dGetChar :: a Char

  dFlushOut :: a ()

  dSetBufferingIn :: BufferMode -> a ()
  dSetBufferingOut :: BufferMode -> a ()
  dSetBufferingBoth :: BufferMode -> a ()

  dSetEcho :: Bool -> a ()

instance MonadDirectedIO IODirector where
  dPutStr s = IODirector $ \hs@(_,hOut) -> do hPutStr hOut s
                                              return ((), hs)
  dPutStrLn = dPutStr . (++ "\n")

  dGetLine = IODirector $ \hs@(hIn,_) -> do r <- hGetLine hIn
                                            return (r, hs)
  dGetChar = IODirector $ \hs@(hIn,_) -> do r <- hGetChar hIn
                                            return (r, hs)

  dFlushOut = IODirector $ \hs@(_,hOut) -> do hFlush hOut
                                              return ((), hs)

  dSetBufferingIn m  = IODirector $ \hs@(hIn,_) -> do hSetBuffering hIn m
                                                      return ((), hs)
  dSetBufferingOut m = IODirector $ \hs@(_,hOut) -> do hSetBuffering hOut m
                                                       return ((), hs)
  dSetBufferingBoth  = (>>) <$> dSetBufferingIn <*> dSetBufferingOut

  dSetEcho m = IODirector $ \hs@(_,hOut) -> do hSetEcho hOut m
                                               return ((), hs)

It’s basically a glorified State monad, and I bet I could even probably extend the extant State monad to let me do this if I really wanted to, though I’m not sure about the threading .. more on that in a second.

Its function is to let you specify an input and output Handle (e.g. (stdin,stdout)) which will be used for I/O within the context of the monad. The benefit here is not needing to thread the Handle pair throughout your code, and they get passed all the way down.

As this is my first monad, I had a bit of difficulty working out what everything should be: there was the new type, IODirector a, which actually represented the stateful computation, then making IODirector (and not IODirector a) an instance of Monad. Must remember that Monad takes a type constructor (* -> *).

Next were the difficulties in threading IO through/in/about IODirector. I knew that I had to do it, I just didn’t know how, or where. Reflecting on the newtype declaration now, it seems obvious that the type it wraps is (Handle,Handle) -> IO (a, (Handle,Handle)), which is just a way of saying α -> IO β for some α, β—essentially, any other I/O action which takes an argument. Next was working out where to return values into the IO monad correctly, but again, on reflection it’s clear that it’s in returning the aforementioned stateful computation’s result that it needs to be wrapped into IO, and indeed, that the entire computation therein is a part of IO. Simple!

The binding rules as a part of IODirector’s Monad instance take care of the threading (and indeed, look exactly like the State monad’s bind/return)—then only the functionality needed to be added. Though not required, I encapsulated the requirement for acting as a “MonadDirectedIO” in a type-class of the same name, and then made an instance of it on IODirector.

I lastly had some difficulty in working out how to correctly define dSetBufferingBoth in point-free form: I was trying all sorts of things involving sequence and various monoid and monad constructs, but was repeatedly running into a brick wall because I never involved (>>)! Duh. Applicative functor to the rescue. I’ve already done this before with more boring functions, so I should’ve realised this a bit earlier (as I’d already defined it as dSetBufferingBoth m = dSetBufferingIn m >> dSetBufferingOut m, so it should have come a bit more quickly …).

Here’s what you can do as a result:

main :: IO ()
main = do
  runIODirector myIoFunc (stdin,stdout)
  return ()

myIoFunc :: IODirector ()
myIoFunc = do
  n <- myNamePrompt "I am an IO func: "
  dPutStrLn ("Hi " ++ n ++ "!")
  return ()

myNamePrompt :: String -> IODirector String
myNamePrompt n = do
  dPutStr n
  dFlushOut
  r <- dGetLine
  return r

You can see that the type-signatures are exactly the same as they would be for a normal IO-centric process, only IO is now IODirector, and the I/O functions themselves are prefixed with d. It’s also trivial to change the in/out channels, if you so wanted, by adding dPut in the same vein as State’s put.

This fun was had while writing a small Go game in Haskell, just to get some real practice with the language. Many thanks to Miran Lipovača’s Learn You a Haskell for Great Good!

Onward!

A follow up on IBM

To be fair with my previous post by giving the whole story now: I called IBM. Less than 3 minutes were up, and I had everything I needed to know about my service call. That time includes time spent listening to their menu tree.

So, incredible phone support; terrible email support. Interesting how they can go so right and so wrong.

I realised something today: Ruby is my work language. I remember years ago when a group of people were discussing, I think on RubyInside (or maybe just ruby-talk), how to get Ruby into the workplace. There was Ruby Insurgency by Andy Hunt—when I review it now, it’s more or less exactly how I introduced Ruby at my workplace. It started off being used by me to do quick little hacks here and there, prototypes and the like; then I introduced it in more mission-critical places one-by-one until it formed a keystone of many of the pieces of architecture.

We have a sizable amount of code that works in production (our testing framework) entirely written in Ruby—its size is of equal magnitude with the software it’s testing. Preprocessors running over all our production code are written in Ruby. The glue that holds our pieces of architecture together are written in Ruby. We’re at the last stage, “Ruby Rules”, of the Ruby Insurgency.

And I can’t enjoy it anymore. Sad, but true. I love OCaml—I don’t think I can actually code in any other language, any more, and have the same feeling of joy that I get with ML, because it’s a very specific one, and Ruby and other dynamic languages can’t deliver it. I don’t think Ruby will be replaced anytime soon as my desktop calculator and ultra-fast script for batch processing and other text analysis, but this basically reduces it to a glorified Perl. Which, I suppose, it is.

I’ve been known to espouse the various joys and delights of Ruby’s object model, but the reality of the matter is that I rarely use it in the use-cases for Ruby that I have left—when I do, it tends to be only because the script is explicitly for one-time use or insular use, and thus will feel no restriction in appending a dozen instances to String or Class or so on. The supposedly great things that I tout the language for are the ones I use least in larger-scale projects.

Of course, this is somewhat a lie—I do use them in larger-scale projects, such as swiftest—but it’s exactly my point that it’s a work thing. While I’ll admit that I don’t have the ML nous to write anything of the complexity or size of swiftest in ML, I’m working my way very readily there in my own spare time (latest achievement: fairly complete (though minimal) lisp interpreter!), and it was only because I had the requisite knowledge on Ruby that I was able to contribute swiftest in Ruby.

That may sound obvious, but the revelation behind it is this: Ruby didn’t let me build swiftest—I did. Anyone could build a similar system in their language of choice, and while naturally the instrumentation of the resulting system and how it would look and feel would sure differ, their end result would be the same, and I daresay a lot of the architecture in any one system would map more-or-less directly onto the architecture in another. I feel the need to draw a parallel with convergent evolution here, though I think one would be neither necessary nor correct, but perhaps you can feel what I’m trying to say: even with a different set of primitives and ideals or motivations at the language level, once you start building greater levels of complexity, you tend to end up with similar abstractions, even if they’re composed in different ways.

You might wonder what draws me to OCaml. It can’t escape all the points made above, right? Well, probably not. But it jives with me even more than Ruby did when I first encountered it—and that’s not to say that Ruby jives with me any ‘less’, per se, but rather I’ve realised that I can jive with a programming language a lot more than I’ve been assuming for a long time. Jive.

I’d like to elaborate on this some more, soon

Below is the email to my company and its sister company which summarised my recent findings with IBM. My email to IBM, 9:35am:

Hi there,

I recently submitted a request with ESC+, problem number 616P496RCS.

When I spoke to the IBM representative on the phone, I requested a change of address – he did this by closing the old ticket (now in status “CCC”) and opening a new one, with number P496CBC.

Unfortunately, the new ticket (P496CBC) is not shown in the “View my requests: Australia/New Zealand” view in ESC+, so I can’t track what’s happening with my laptop.

As it has been over a week, I’d like to know what’s happening. Thanks!

Cheers,
Arlen

At 9:43am, IBM’s reply graced my inbox.

Dear  Arlen
Thank you for contacting AskIBM.

For technical enquiries, warranty claims, Recovery CDs, repairs and local IBM Repairers in Australia please contact our service centre on 131 426 (61 7 5585 3144).

For technical and service enquiries in New Zealand, please contact 0800 733 222  (64 4 576 5555).

Should you have any further enquiries please do not hestitate to contact AskIBM.

Regards

Jane
AskIBM Administrator
IBM Australia

I replied at 9:50am:

Hi Jane,

Thanks for your reply! I do have further enquiries, as it happens.

Are you able to help me at all via email? I don’t particularly want to spend all day on the phone, which is why I went to the trouble of finding an email address where I could actually contact you guys.

Your response gives the impression you didn’t actually read what I wrote at all. (Case in point: I didn’t ask for phone numbers.)

Thanks again,

Arlen

At 10:32am, IBM struck back:

Dear  Arlen

Thank you for contacting AskIBM.

For  technical support and service please contact:

131 426   (61 7 5585 3144)  if calling form Australia or

0800 733 222  (64 4 576 5555)  if calling from New Zealand.

Regards

Jane
AskIBM Administrator
IBM Australia

With my dear friend Alex’s help (i.e. he composed the entire thing), we vetoed her attempts to palm us off at 10:42am:

Dear Jane,

Thanks for getting back to me, and for again ignoring the main thrust of my email.

I apologise for the tone of this email, however your latest response has left me feeling undervalued as a customer.

I cannot see where the issue would be in having a level of basic manners and responding with “I’m sorry, but we deal with our technical queries via phone, please contact etc etc” rather than ignoring my question and responding only with the contact details.

You will note that my response to you, whilst acknowledging your actions in the conversation, also contains my own questions. Note how from my point of view this could be considered an open dialogue, whereas your responses provide me with no added benefit beyond that which an auto-responder would provide.

Moreover, your responses contain typos which make it clear that I am being responded to by a human. This adds insult to injury, as it means not only are my responses reaching a person, but that person is taking deliberate steps to ignore my questions.

So please – if I must contact your phone support (which I dearly hope is better than your email support) just answer me clearly. Do *not* give me the phone number again – it is apparent that I already have it, as it’s the only thing of any value you have thus far given me. Tell me not only that I must contact phone support, but that my continued emailing will have no effect but to further frustrate me.

Regards,

Arlen

At 11:07am, IBM raised their white flag in a pitiful act of cowardice:

Dear Arlen

Thank you for contacting AskIBM.

I am unable to provide an email address.

Please phone our service centre.

Regards

Jane
AskIBM Administrator
IBM Australia

This is why we rock.


Arlen Cuss
Software Engineer
Noble Samurai

German efficiency

DHL turned up just now (before 2pm) for a pick-up. I’m hereby assuming it was for me.

It was quick, but man, what an attitude.

Me: Are you from Lenovo?
DHL: I’m from DHL.
Me: O…kay… who does it say the pick up’s for?
DHL: Byte. (or something that sounds like that)
Me: Byte?
DHL: Byte.
Me: Alright..

I hand over the laptop, without battery and AC adapter as requested on the phone earlier today.

DHL: You’re lucky I’ve got a box, otherwise that’d be bouncing around in there!
Me: …… (they said on the phone he’d have a box??)

That’s it. Fast but unfortunate courier.

Den mänskliga hjärnan

I learned a funny thing about the human mind this morning.

Last night I was trying to lodge a service request with IBM for my ThinkPad Edge—very, very poor quality, if I do say so myself. From a few days ago, the screen started blanking (with the laptop going into suspend) at random, though it seemed to happen most often while Misty and I were watching a DVD. It’d happen when I was using the keyboard, when I wasn’t, DVD or no DVD, eventually becoming more and more common.

This started to really frustrate me, coupled with the fact that Linux 2.6.32 seems to have a 1 in 3 chance of failing to resume from suspend on it. “Preferences -> Power Management” lets you stop it from suspending (it only locks the screen), but that was still really annoying. It turns out gnome-power-management has keys in gconf where you can actually disable any behaviour at all—I discovered that yesterday. That was ideal, but the word “ideal” is laughable when it meant that, by this stage, the LCD backlight would turn off after a few seconds of use (and with it the external monitor also turns off—the computer seemingly under the belief that I’m closing the lid?), and it would take a lot of moving the laptop’s lid back and forth before I’d just strike an angle that would leave it on for a few seconds more.

I had a go at taking it apart, but I couldn’t find the mechanism that signals whether or not the lid is closed (nothing obviously magnetic, either). I hadn’t seen any of this behaviour while using Windows on the machine, so I tried rebooting into Windows, but the symptoms were steadily getting worse.

I decided it high time to get IBM onto the scene (as they provide support for Lenovo’s machines, the two being mostly one and the same, now). I discovered that applying a strong pressure to the part of the laptop just to the right of the keyboard (near the return key and so on) actually caused the LCD to work. I had to keep it there though. This was frustrating.

So, there I am, frustratingly trying to navigate Lenovo’s support website (to lead me to IBM’s “Electronic Service Call+” website), trying to login, all with my right hand applying a firm pressure to this area right next to the keyboard. No fun.

I imagine that, when I signed up to Lenovo’s website back when I purchased the laptop, that ID may extend to IBM’s website, so I try logging in with that email address. No deal! I can’t find any password configuration that works. I choose “Forgot my password”. And here’s where the whole point of this entry comes in.

My secret question comes up, and it looks nothing like a secret question I’d ever set:

(3 * 2) * (3 * 1.5 * 2) =

That’s it. I look at it and think—surely this isn’t mine. The email address sure is, though. It annoys me that they have no recourse of “send password reset link to email”. Working from the left, I get 3×2=6, 6×3=18, 18×1.5=27, 27×2=54. I enter “54″. No dice. “fiftyfour”. Nope. “fifty four”. Nuh-uh. “fifty-four”. Nothing works.

Annoyed, I give up and register for a new account with my work address (this is all with my hand on the right side of my laptop). It takes an agonisingly long time to do that, and then even longer to lodge an “electronic service call”, the form for which seems designed more for companies with thousands of IBM assets than anything else. They even asked me for a “priority”. Sure, I’ll pick “highest”.

This morning, I wake up after some really, really strange dreams, and as I slowly manage to come to reality, Misty and I start chatting. Half-way through a sentence, I realise my brain has been working out the equation as it was written; by this stage I couldn’t remember the right hand side, but I remember that it was 6x=54 and—of course, 6 × 9! Though I’ve not heard the radio play in years, nor read the books, The Hitchhiker’s Guide to the Galaxy came to me at once, and I knew the answer must be 42.

I sprang out of bed and found the log-in form, filled out all the information, and voilà—success.

The human mind sure is strange.