Sunday, August 25, 2013

Deal Journal - Part One

I already mentioned Lisp In Summer Projects, and called it

...like a multi-month NaNoWriMo with parentheses instead of character development and sleep.-Inaimathi

The project I picked out wasn't something I'd ever talked about here before. It was something a friend of mine and I were thinking of putting together to make his hobby/job slightly easier. He makes tabletop games you see. Mostly card stuff, but potentially other tabletop stuff too, from what I gather. This is to be the running journal of my project as I'm writing it. I'm not too worried about it denting my motivation, because I don't intend to publish it until I'm done.

To be perfectly honest with you, Lisp wouldn't be my first choice for this. I mean, the language is always a good thing to have in your corner, but there's a notable lack of battle-tested, feature-full, asynchronous web-servers for it. There's Antiweb, if you want to get down into the nuts and bolts of the system and serve things at the most efficient possible rate, at the expense of more complex installation and configuration. There's Wookie, if you don't particularly care about speed or security. There's sw-http, which I've been warned off of directly. And there's Hunchentoot if you don't care about being asynchronous. There's no Common Lisp equivalent to Warp or Yaws or Tornado, and I'm fairly comfortable with each of them, so if not for this contest, this probably would have been a Haskell/Elm, or perhaps Erlang/Angular.js project rather than a CL/Parenscript one.

I'm not too worried. The only part of this system that capital N needs to be asynchronous is the SSE handler I'll be using for browser pushes, and I'm fairly confident I'll be able to tweak Hunchentoot slightly to offload those onto a single, dedicated thread rather than keeping each one running in its own.

The Approach

I want to battle-test some of my own ideas. Starting with the front-end/back-end separation I've been on about for a while, and continuing with some notions I've had about self-documenting APIs. To that end, deal is going to be a pair of projects. A game server implementation which will huddle behind nginx, deal with the application requests, and whose handler definitions are going to be simple enough to read that you'll be able to. And a reference-implementation of a web UI that will communicate with that server and do useful things in a browser.

Now then, without further ado.

The Journal

Day One

So here's the minimal amount of stuff we need to model in order to be a useful play-testing tool:

  • cards
  • collections of cards (I'm going with "stack" for the moment)
  • hands (different from stacks in that they're not on the table, but being held by players)
  • players
  • die-rolls/coin-flips
  • counters/notes

And we need to be able to interact with each one in a variety of ways.

  • rotate/move/flip cards and collections ("rotate" as in "on an axis", "flip" as in "from face-up to face-down or vice-versa")
  • play (either face up or face down)
  • play to (onto a stack rather than onto the board directly)
  • pick up
  • shuffle (this one just applies to a stack)
  • peek (a player looks at n cards of a given stack)
  • show (all players see n cards of a given stack)
  • re-arrange (peek at n cards and put them back in an order you specify)

Each line of that second group needs to be a handler. Each line of the first group needs to be represented somewhere. Despite my confidence, I'm not entirely sure I won't be porting away from Hunchentoot if hacking SSE support into it turns out to be too difficult, so I'd rather define a little sub-language for handler definitions than call define-easy-handlers manually. While I'm at it, let that mini-language take type-hints so I don't have to deal with chucking strings around myself. The initial version of define-handler does simple type conversion, and thinly wraps define-easy-handler

(defmacro define-handler ((name &key (default-type :integer)) (&rest args) &body body)
  (let ((opts `(,name :uri (concatenate 'string "/" (string-downcase (symbol-name name))))))
    (if (not args)
        `(define-easy-handler ,opts nil (encode-json (progn ,@body)))
        (flet ((type-exp (arg type)
                 (case type
                   (:integer `(parse-integer ,arg))
                   (:string arg)
                   (:keyword `(intern (string-upcase ,arg) :keyword)))))
          (let ((type-conversion (mapcar (lambda (a) 
                                           (if (atom a) 
                                               (list a (type-exp a default-type))
                                               (list (car a) (type-exp (first a) (second a)))))
                                         args))
                (final-args (mapcar (lambda (a) (if (atom a) a (car a))) args)))
            `(define-easy-handler ,opts ,final-args
               (let ,type-conversion
                 (encode-json (progn ,@body)))))))))

(defmacro define-game-handler ((name &key (default-type :integer)) (&rest args) &body body)
  `(define-handler (,name :default-type ,default-type) (game-id ,@args) ,@body))

And it lets me write things like

(define-handler (play/move) (thing-id x y z rot)
  (list :moving thing-id :to x y z rot))

and have it mean

"give me the Integers thing-id, x, y, z and rot, and I'll give you a JSON-encoded response of the list ':moving thing-id :to x y z rot'"

That's it for day one.

Day 3

I skipped one. In truth, this is a few days later, and I have been throwing hours/half-hours at the problem in the meantime, but getting no dedicated time down.

The type annotations are a good idea here, I think. Even in a dynamically typed language, you want to surround any kind of outside input with assertions or similar, and being able to read the types is going to help people trying to interact with your API. The separate handler definition macro for tables was a misstep though. All it actually does at this point is provide a with-lock around the body, and add an invisible argument of (table :table) to whatever you define with it.

(defmacro define-server-handler ((name) (&rest args) &body body)
  "Specifically defines handlers dealing with global server state.
Shares similarity with define-table-handler (if another one comes along, we'll abstract this)"
  `(define-handler (,name) ,args
     (with-lock-held ((lock *server*))
       ,@body)))

The first is bad because you don't always want a lock with a table. For instance, when you're serving up an EventSource, it would be a phenomenally bad idea to keep a lock on the related table. The second is bad because we're trying to make this self-documenting. Which means that, while invisible arguments are going to save some typing, they'll be just a little bit more annoying to any front-end developers who try to develop against our server. So, this has to go.

There's also the point that my existing type annotations aren't saving me as much work as they could be. Specifically, whenever I ask for a foo-id, I end up looking it up in the appropriate place; either (things table), or possibly (hand *player*)[1], then assert that the thing coming out of the lookup is the sort of thing I'm expecting, then I do something to that thing. The "type" system really should be able to do this for me.

(defun type-exp (arg type)
  "Given a symbol name and a type, returns the expression to read that type from a string"
  (match type
    (:string nil)
    (:int `(parse-integer ,arg))
    (:json `(decode-json-from-string ,arg))
    ((or :keyword :facing)
     `(intern (string-upcase ,arg) :keyword))
    (:table 
     (lookup-exp arg '(private-tables *server*) '(public-tables *server*)))
    ((or :stack :flippable :placeable
         (list :card :from-table))
     (lookup-exp arg '(things table)))
    ((list :card :from-hand)
     (lookup-exp arg '(hand *player*)))
    (_ (error "Invalid type label: '~a'" type))))

(defun lookup-exp (arg &rest places)
  (with-gensyms (sym)
    `(let ((,sym (intern ,arg :keyword)))
       (or ,@(loop for p in places
                collect `(gethash ,sym ,p))))))

(defun lookup-assn (arg type)
  (match type
    (:table `(assert ,arg))
    (:stack `(assert (typep ,arg 'stack)))
    (:facing `(assert (or (eq ,arg :up) (eq ,arg :down))))
    (:placeable `(assert (typep ,arg 'placeable)))
    (:flippable `(assert (typep ,arg 'flippable)))
    ((list :card _) `(assert (typep ,arg 'card)))
    (_ nil)))

(defun type-pieces (args)
  "Takes a list of arguments and returns three values:
- The conversion expressions
- The names (for use as final args)
- The lookup assertions"
  (loop for (name type) in args
     when (aif (type-exp name type) (list name it)) collect it into convs
     collect name into as 
     when (lookup-assn name type) collect it into assrs
     finally (return (values convs as assrs))))

(defmacro define-handler ((name) (&rest args) &body body)
  "Defines handlers with an eye for self-documentation, DRY and portability"
  (let ((opts `(,name :uri ,(concatenate 'string "/" (string-downcase (symbol-name name))))))
    (if (not args)
        `(define-easy-handler ,opts nil (encode-json (progn ,@body)))
        (multiple-value-bind (type-conversion final-args lookup-assertions) (type-pieces args)
          `(define-easy-handler ,opts ,final-args
             (assert (and ,@final-args))
             ,(if type-conversion
                  `(let* ,type-conversion
                     ,@lookup-assertions
                     (encode-json ,@body))
                  `(progn ,@lookup-assertions
                          (encode-json ,@body))))))))

And it can.

The other thing I'm finalizing is the id system. An earlier crack just had each component keep count of its contents and assign that as the next id. There are a few obvious problems with this. Firstly that it would result in duplicate ids sometimes. Secondly, unless I wanted to update the item id every time I moved the item, this would mean a global counter in *server*, which would mean a lock on the whole server any time anything changed play zones. The change I ended up making is just using gensym. Ordinarily, I wouldn't but: these ids don't need to be cryptographically random, they just need to be unique with respect to all other active ids. Of course, doing it this way is going to run me up against potential problems when I get to loading games from disk storage, but that's a pretty long way off. Anyhow, as a result, all the foo-id and id fields are now keywords rather than integers.

Day 4

First stab at the interface. And by "first stab", I mean "stupid basic interface that quote renders end-quote things by echoing them to console". It's nowhere near complete, but it's already enough to iron out a wrinkle or two. Specifically, I've had to go back through the model and change every belongs-to slot to expect an ID rather than a pointer to a player. It became obvious that this was necessary when I got memory-use warnings followed by a crash when I tried to "render" a card. encode-json-to-string doesn't like circular references, you see.

Now that everything uses IDs, there's one semi-obvious good thing about it: it'll make putting together the front-end much easier. Because the IDs are now globally unique, I can use them as a class tag in the DOM to identify objects on the board. That'll let me update the state of a lot of things in the UI without having to re-render very much at all.

Day 6

I've been refining the model a bit to take into account some of the games I'll want to model for this project. There's also a slightly revised define-handler macro that stores information about any handlers it defines, which then gets served through the list-handlers handler. That'll make certain parts of the front-end easier to put together.

Not much work other than that, sadly. I'm still moving forward in increments of an hour or half-hour at the outside. What I have been able to do is read through pieces of the Hunchentoot code to try figuring out how, exactly, to hack conditional SSE support to it. Near as I can tell, I'll need to define a :before method for handle-request and then figure out how to let its call chain know not to terminate the appropriate socket stream. Something else has occurred to me though. Because there's really only one handler I'm going to need to be served asynchronously, and that handler will only serve up public information, a reasonably simple approach here might be to just off-load SSE serving to something better suited for it, specifically. Yet another approach, since I'm considering aleph, is to just write the whole thing in Clojure to begin with...

Fatherly Interlude

My son is at a stage where everything he gets his hands on automatically goes in his mouth. Food, toys, cats, carpet, the computer I got him to paw at. Everything. He's also gotten to teething, which seems to be a very painful experience judging from his vocal emissions.

Day 9

The past few days have been mostly prospective development and a little thought about secrecy. The end result is going to be some minor mechanical changes to how ids function, and they won't be shown for cards inside stacks.

Let me try to take you through it. What I was thinking earlier is that I can just assign a canonical ID to each thing that needs to go on the table. The trouble with that approach is that it canonically identifies a thing. So, for example, if you take a card from the table, put it into a stack, shuffle that stack, and then play a card face-down, it will be possible for each player to tell whether it's the same card. If it has the same id as the starting card, everyone knows what it is, otherwise, no one knows what it is but they can at least knock one option out of the possibility space.

This is not what you want.

The default for that situation is that no one should know what the card is, or have any additional information about it. There are two ways to solve this:

  1. We could create canonical ids for everything, but display a salted+hashed version to the front end, changing out the salt whenever the zone of play changes. That would let us keep a single id in the back-end, but it would keep everything reasonably anonymous to the front end. It seems kind of expensive, and complicated, and not particularly useful in any case.
  2. We could assign a new id to a thing when it crosses play zones. So, for example, when you play a card, it gets a new id while in play. If you then put it into a stack, it gets a new id while there. If you play it face-down out of the stack again, that's a third in-play id.

We don't actually need a central way of addressing a given thing. Or, at least, we don't yet, so I'm inclined to go for this second option. Remember, we generate ids through gensym, which is a pretty cheap computation as far as I know. We could, of course, keep our own global counter as part of *server*, but I'll see if that's necessary later. What I might want to do at the moment is name the function make-id just to make it a bit simpler to change if we end up needing to.

Day 10

I've been thinking about the SSE situation, and it occurred to me that since

  • I'd only need one SSE channel per game
  • It would contain only public data
  • I would want it to support spectators (and therefore wouldn't want to restrict access to it)
  • I plan to deploy Deal by running a reverse-proxy from nginx

it wouldn't be a bad idea to off-load that particular handler onto nginx itself. The ideal situation would be one where I could just serve up a file per game as the "stream", then keep appending to it from within Deal. That doesn't seem to be trivially possible, but nginx does have an optional, production-ready push_stream_module licensed under GPL3. That's something to consider, since it would really only take a bit of configuration twiddling as opposed to actual code to get this up-and-running.

Day 12

Ok, I'm ignoring the SSE question for now; we don't really have any call for it until I get enough of a front-end together to support more than one player in any case. That's proceeding apace. I've been thinking about how to approach this task; should I abstract as much and as aggressively as possible, or should I keep it plain, straightforward and stupid? Typically, I go for the second option if I can help it at all, but I decided to go the opposite way this time. Here's a list of utilities I defined. Mostly thin wrappers around existing jQuery constructs, and two very tasty pieces of syntactic sugar to help me define things.

(in-package #:deal-ui)

(defparameter *debugging* t)

(defpsmacro log (&body body)
  (when *debugging*
    `(chain console (log ,@body))))

;;;;;;;;;; JS Basics
(defpsmacro obj->string (thing)
  `(chain -j-s-o-n (stringify ,thing)))

(defpsmacro string->obj (thing)
  `(chain j-query (parse-j-s-o-n ,thing)))

(defpsmacro fn (&body body) `(lambda () ,@body))

;;;;;;;;;; jQuery Basics
(defpsmacro $ (selector &body chains)
  `(chain (j-query ,selector) ,@chains))

(defpsmacro doc-ready (&body body) 
  `($ document (ready (fn ,@body))))

(defpsmacro $map (lst &body body)
  `(chain j-query (map ,lst (lambda (elem i) ,@body))))

(defpsmacro $post (uri arg-plist &body body)
  `(chain j-query 
          (post ,uri (create ,@arg-plist)
                (lambda (data status jqXHR)
                  (let ((res (string->obj (@ jqXHR response-text))))
                    ,@body)))))

(defpsmacro $droppable (target &rest class/action-list)
  `($ ,target (droppable 
               (create 
                :drop (lambda (event ui)
                        (let ((dropped (@ ui helper context)))
                          ;; not sure if this should be a cond or a list of independent whens
                          (cond ,@(loop for (class action) in class/action-list
                                     collect `(($ dropped (has-class ,class)) ,action)))))))))

(defpsmacro $draggable (target (&key revert) &body body)
  `($ ,target (draggable (create :stop (lambda (event ui) ,@body) :revert ,revert))))

;;;;;;;;;; Define client-side ajax handlers
(defpsmacro define-ajax (name uri arg-list &body body)
  `(defun ,name ,arg-list
     (log *current-table-id* ,@arg-list)
     ($post ,uri (:table *current-table-id* ,@(args->plist arg-list))
            ,@body)))

;;;;;;;;;; Defining markup/behavior hybrids made easier
(defun expand-self-expression (form self-elem)
  (flet ((recur (frm) (expand-self-expression frm self-elem)))
    (cond ((null form) nil)
          ((atom form) form)
          ((and (eq 'self (car form)) (eq (second form) 'position))
           (recur '(+ "top:" (self y) "px;" "left:" (self x) "px;" "z-index:" (self z) ";" "transform:rotate(" (self rot) "deg)")))
          ((eq 'self (car form)) 
           `(@ ,self-elem ,@(cdr form)))
          ((atom (car form)) 
           (cons (car form) (recur (cdr form))))
          ((listp (car form)) 
           (cons (recur (car form))
                 (recur (cdr form)))))))

(defpsmacro define-thing (name markup &body behavior)
  (deal::with-gensyms (thing container)
    `(defun ,(intern (format nil "create-~a" name)) (container thing)
       (let* ((,thing thing)
              (,container container)
              (css-id (+ "#" (@ ,thing id))))
         ($ ,container (append (who-ps-html ,(expand-self-expression markup thing))))
         ,@(loop for clause in behavior
              collect (expand-self-expression clause thing))))))

<p>The first bunch already kind of got addressed <a href="http://langnostic.blogspot.ca/2011/03/javascript-with-lisp.html">last time I talked about parenscript</a>. Some newcomers include sugar for using map, draggables and droppables in a simpler way than the default jQuery UI package allows for</p>

(defpsmacro $map (lst &body body)
  `(chain j-query (map ,lst (lambda (elem i) ,@body))))

(defpsmacro $droppable (target &rest class/action-list)
  `($ ,target (droppable 
               (create 
                :drop (lambda (event ui)
                        (let ((dropped (@ ui helper context)))
                          ;; not sure if this should be a cond or a list of independent whens
                          (cond ,@(loop for (class action) in class/action-list
                                     collect `(($ dropped (has-class ,class)) ,action)))))))))

(defpsmacro $draggable (target (&key revert) &body body)
  `($ ,target (draggable (create :stop (lambda (event ui) ,@body) :revert ,revert))))

All of the correspondingly wrapped structures suffer from the same syntactic problem; they want you to pass them a function, but that function will always get the same arguments passed to it. In plain JS, you can't really bust out of this pattern without using eval. Which you shouldn't do. If you're dealing with JS through a language like Lisp though, you can just define macros like these to take the appropriate body arguments and then drop the appropriate lambdas around them. As long as you remember what the arguments are, that frees you from having to check documentation on their order every goddamn time I write any serious front-end JavaScript.

define-thing and define-ajax are more complex constructs. The second one is a way for me to define connecting functions between the front-end and the back end. Specifically, it lets me say things like

(define-ajax show-table "/show-table" () (render-board res))

That'll do exactly what you think it should; send an ajax request to the uri /show-table, then pass the JSON-parsed result to render-board. define-thing buys me more of the same, except it's good for defining local UI components rather than asynchronous handlers. Here's an example

             (define-thing stack
                 (:div :id (self id) 
                       :class (+ "stack" (when (= (self face) "down") " face-down"))
                       :style (self position)
                       :title (self id)
                       (:button :class "draw" "Draw")
                       (:div :class "card-count" (+ "x" (self card-count))))
               ($draggable css-id () 
                           (move (self id) (@ ui offset left) (@ ui offset top) 0 0))
               ($ (+ css-id " .draw") (click (fn (draw (self id) 1)))))

Note that this makes use of the $ and $draggable macros as well. What this does is sugar-coat the definition of a function called create-stack, which will take a container selector and a JSON object and

  1. slot the object into that markup specification
  2. append the result to the given container
  3. run the behavior applying code on the newly formed element

I'm still considering having the macro itself add the declaration of :id (self id), because I do that literally everywhere. The only other interesting part is that this macro goes through the trees you pass it and expands anything that looks like (self foo) into something that looks like (@ self foo), which is how you're supposed to index thing in Parenscript. It also special-cases (self position) into the complete CSS style rule, making sure that the x, y, z and rot slots are reflected in the relevant CSS properties.

That's that for now. Hopefully, I can 0.1 this thing fairly soon, and finally publish part one of this journal. I was going to wait 'till the end, but it looks like the complete document will be far too long to publish at once.

Day 37

Kind of a big jump this time. Haven't really had the chance to do stuff related to this project lately. My time's been getting filled with extremely interesting, lispy things that I'm unfortunately not allowed to tell you about. Yet. Hopefully, I can convince the correct humans to let me publish some or all of it in the near future.

I've implemented the session system, which actually lets multiple people sit down at a single table and play together. That's basically it. I've been thinking about what I want the join/new-game interface to look like, but at this point that's all it'll have to be. An interface. The hard part is more or less done. There's one big architectural question I have to answer, and one big feature I need to properly implement, and then I can move on to the task of making the UI pretty, and maybe build some basic tools for deck construction as well as playing.

The Big Architectural Decision

Is whether to explicitly represent stacks in the final model. It kind of makes sense, given that you don't want anyone to know what cards actually get shuffled to, so it's possible to conceptualize "in a stack" as a state change for the card on the table. It still doesn't work that way in real life. You can take a bunch of cards and stack them, but you never lose the ability to interact with each of them individually. There might be one or two things that either view of the world enables or prohibits, but it also seems that it'd be pretty straight-forward to switch between them later if I wanted to. Maybe this is one I hold off on until I see a direct need.

The Big Feature

Is data pushing.

Fuck, I had vaguely hoped that in the year 2013, this would be a solved problem, but none of the options provided natively as part of the http/js/html stack are both simple and compatible with the thread-per-request model of serving up data. I'm still heavily leaning to just using the nginx stream module given that this projects' published data fits some specific criteria that would make a full public solution possible.

That's that. Once those are ironed out, I can finally post a one point oh and get people playing it. Oh, and get this piece published already so I can get on with the next one: taking it from "working" to "beautiful".

Day 38

So the trivial part of the feature is done. It seems that the nginx stream module is easy to set up and get running properly. I haven't restricted publishing rights to localhost yet, but I can't imagine that'll be much more difficult to configure. Now comes the slightly harder part: defining the infrastructure inside of deal to publish to these streams and get new arrivals up and running. The basics will look something like

(defmethod publish-move! ((table table) move &optional (stream-server *stream-server*))
  (push move (history table))
  (http-request
   (format nil "~apub?id=~a" stream-server (id table))
   :method :post :content move))

Except that I think I'm going to make move itself a JSON object just to make it easier to work with on the other end. The *stream-server* variable will then be set to the location of the nginx instance that handles stream serving for me. Note two things about this setup, incidentally:

  • the nginx stream module natively handles multiple protocols. By default it uses a forever-frame, but it can be configured to expose the same stream as an EventSource[2], and a web-socket, and a long-poll handler.
  • the server handling my stream publishing doesn't have to be on the same machine as the rest of the application, which opens up some interesting hosting possibilities if scaling up ever gets to be the problem I'm staring down

It also really, truly looks like it'll be both more performant and much easier than trying to re-write pieces of Hunchentoot to support asynchronous requests in certain contexts.

Day 41

I have no idea what happened, but I finally ended up getting a solid day to put stuff together for this project. As a result, I've got a pretty-much-playable edition sitting up on my server, waiting for a couple more edits before I unveil it, and this massive Journal: Part One I've had going. Right now, I'm in the guts of the define-handler mini-language, trying to get my pseudo-type-system to automatically solve the problems of argument bounding for me. That is, I want to be able to specify the min and max for various argument types and have it do the right thing. Specifically, I'd like to be able to specify minimum/maximum values for :ints, and minimum/maximum lengths for :strings.

The :int changes only come into play in the new-table handlers, and the dice-rolling system. I don't want people to start tables that seat fewer than 2 or more than 12. Also, I don't want people to be able to roll 2>-sided dice, or fewer than one of them. A d2 is a coin-flip, which I have a separate handler defined for, and any less than that would be entirely too predictable. That's pretty obvious: assert that the incoming parameter fits within the specified range, and we're done.

The :string changes are going to be used as part of chatting and tagging. Chat messages are going to be delivered from the user to the named table/lobby, and tags are user-specified strings that will be applied either to themselves or games they start. Tags can be empty strings[3], but chat messages need to be at least two characters. And neither thing should ever be longer than 255 characters[4]. Now, if I get a chat message shorter than I want it, that's obvious: just throw an error and do nothing.

But.

What do I do with a string longer than I want? There's two reasonable-sounding ways to handle that situation

  1. Error out; after all, interface this user is piloting doesn't conforming to my API, so it should come as no surprise to anyone
  2. Truncat; take a chunklet of whatever they sent small enough for my purposes, and proceed to fulfill the request with only the relevant data

Erring means chat messages get dropped, truncating means something goes out over the wire, even if it wasn't exactly what the user intended. Now that I think about it, it seems obvious that what you'd really want, as a user, is for the server to be hard-assed about it, but the front-end to tell you what's going on. In the interests of loose coupling, this means I actually want to specify that limitation in both places. Which works perfectly, because my server already emits the specifications for its handlers through /server-info requests, and that will automatically include any mins/maxes I define in the relevant argument lines.

Day 42

Basically, finished a bunch of the UI changes I needed to make in order to get this into a playable state. Not quasi-playable, not semi-playable, just plain playable. You can actually go here and use it for realzies. I mean, it's not enjoyable yet, and there's a lot of basic functionality still missing[5], but you can actually go there with a couple of friends, start a game of crazy eights or something, and have an excellent chance of finishing it before anything crashes. If anything crashes, incidentally, do report that. Or patch it and send me a pull request.

I've got a bunch of things still in my head concerning where this project ought to go. Some of them involve more degrees of freedom in terms of the reference UI I've been putting together, one of them is a deck builder (which it'll need to fulfill the "prototyping" promise of this project), and another is a board position editor (which it'll need to fulfill the "prototyping" promise of this project for anything other than card games). Now that I think of it, those last to could possibly be combined elegantly. Hmm.

Anyhow, so concludes part one of my journal: zero to playable. Now I'll try to take it from playable to as close to beautiful as I can before the contest deadline is up.

Wish me luck.


Footnotes

1 - [back] - This second one will change, incidentally. In the real system, this will be referencing a player record from the current users' session rather than the global one, so it's an even better idea to handle that in a macro rather than manually as part of each handler.

2 - [back] - Which is basically a formally-specified forever-frame with direct JavaScript support in modern browsers.

3 - [back] - The appropriate id gets used in that case so that there's an unambiguous way to refer to a player or game, if you're wondering, tags are just supposed to provide something human-readable.

4 - [back] - Arbitrarily chosen. It's what all the cool kids were doing, and it serves my purposes well enough, so I went with it.

5 - [back] - Such as changing your screen name, playing things face down, picking things up, coin-flips, dice rolls, and pretty much anything other than playing the standard 54-card deck.

Wednesday, August 21, 2013

cl-web-dev

Extremely short post. Seriously, not so much as a self-referential footnote this time.

I've been hard at work on deal, when it occurred to me that I've written at least some of that stuff before. Pretty much every web development project I've started in Common Lisp in the past few years has had certain pieces of low-level helper code baked in. And I got sick of it.

So, here's cl-web-dev a small collection of functions and macros to make it marginally more pleasant to deal with hunchentoot, cl-who and parenscript. The bare-bones "Hello World!" for it is

(ql:quickload :cl-web-dev)
(defpackage :your-package (:use :cl :cl-web-dev :parenscript))
(in-package :your-package)

(define-handler test ()
  (html-str
    (:html
      (:body
       (:h1 "Hello World!")
       (:p "From" (:code "cl-web-dev"))
       (:script (str (ps (alert "And also, parenscript"))))))))

(defparameter server (easy-start 4242))

Which starts a server on local port 4242, and sets up that handler at /test. I could probably hack a pretty big chunk out of deal, but I think I'll wait on that until after the contest has ended.

Thursday, August 15, 2013

Debugging Insecurities

I don't know if anyone else does this, but I constantly catch myself doing it. Even when I should really know better by now.

1. Write Some Code

That's my usual, and it does feel pretty good. I'm producing code and getting things done. Properly. Not just the barest possible solution that could possibly work, but taking approaches that I haven't before and seeing if they yield implementation or performance improvements.

2. It Doesn't Work

Of course it doesn't work, this is the first time I'm trying the technique, and no tech starts out perfect. If anyone tells you otherwise they're either lying to you or themselves, and either way I'm not dealing with them right now. Even after running through this loop several times, it still takes a conscious effort not to get pissed off at the new technique, or some part of the toolchain. It never turns out to be any of those things, but there's still a hard, deep-wired reflex to look for something opaque to point to as a source of my problems. That would be a fail though. So I exert the conscious effort to suppress that reflex in the interests of learning something.

3. Debug

Hop into the debugger, or the REPL, and start poring over all the interaction metadata I can get my grubby little paws on. In C, it means setting breakpoints and following them. In Common Lisp it means running the code piecemeal through SLIME, optionally with logging :before and :after methods defined everywhere I could possibly define them. In Haskell it means reading the compiler output and asking someone who knows what the fuck they're doing what it means.

4. It Still Doesn't Work

And of course it doesn't work again. I find a couple of superficial things to fix, each one reducing the number of warnings I get, but none ever solving the root of the problem.

5. Iterate 3 and 4 with a dwindling faith in my understanding of the world

Somewhere between the second and fifth iterations of the previous two steps, I stop believing that I understand the language I'm using. That such an understanding is even possible for a mere mortal such as myself. I start thinking that maybe I have some piece of basic understanding about the insides of computers and/or compilers fundamentally backwards, and that no amount of poking will ever save me. I should go back and take some high-school level Comp Sci courses, or maybe just drop the whole "Developer" thing and go find a job more my speed, with shiny buttons and tabs to click on all day instead.

6. Oh, there it is...

Eventually, find the last piece of error-ridden code hiding two or three layers deep in a place that I changed incorrectly a while back. And then it works. And then I have to go back through the intervening code just to convince myself that my understanding was not, in fact, some sort of decade-long mirage which merely fooled me into thinking that I occasionally knew what I was doing.

That happens disturbingly often. Which is not to say that I have lots of errors in my code, oddly. They tend to come few and far between, but the percentage of them that trigger this crisis of confidence in literally everything I know is huge. Easily in the 90% range. I have no idea why this happens or how common it is for other humans, but I find it afflicting me often enough that I finally had to write about it.

I also have no idea what to do about it.

Sorry.

All the alternatives seem worse. Having iron self-assurance in these situations would end with blaming a blameless component for the error and never actually figuring out what went wrong at any level even approaching a deep understanding. That's too high a price to pay for the small comfort of considering myself to be smarter than I am. There's a Stross quote that I particularly like, and I'm going to strip it of context for you here

To never harbor self-doubt is poison for the soul, and these aliens want to inflict their certainties upon us.--Sadeq, Charles Stross' Accelerando

There's a bunch of ways you can read that, including literally in context where it refers to a specific group of actual aliens, but that's not what it means to me. My imbued meaning is: Doubt is the strongest elixir of knowledge available to me. It exacts a price on your sense of certainty, but in return lets you face the kind of complexity and understanding that would evade lesser analysis.

So I guess the answer is not to do anything about it. My doubt needs to stay where it is, for the sake of my intellectual development.

Saturday, August 10, 2013

Forthlike and Briefly, Keyboards

So I got a new keyboard.

All told, it ran me something in the area of $250. Not sure I consider it worth it, but I've only really typed on it for a solid day so far, so that's probably not enough experience to make a call about it. So far, my impression is that it is an improvement over the Cherry MX blues I've tried, but not quite ~$150 worth of improvement. If you've got some cash burning a hole in your pocket, and a need for more comfortable typing, I can heartily recommend it to you. It's very comfy, the Topre keys feel great, there's dip-switch support for swapping the Caps Lock and left Ctrl keys[1]. It also costs quite a bit less than the HHK2, which I would totally order if someone dumped a million dollars on me tomorrow, but as it stands, $400 is out of my price-range for a keyboard.

Forthlike

Nothing serious here, just some thinking and playing I've been doing.

At the last meeting, a fellow Toronto Common Lisper presented an idea of his for a language titled FNFAL. The FuNctional Fixed Arity Language. Its primary goal is to be extremely simple to implement, while also not being quite as alien as Forth or Scheme to the uninitiated. Someone made a comment to the effect that Forth was extremely easy to implement, which sent me off thinking about how easy it actually is.

I pointedly didn't read the spec, but I have read a few forth tutorials and I have vigorously poked at GForth once or twice.

Anyhow, the answer is "not very hard", assuming you start with a high-level language and don't adhere to the standard[2]. The entire exercise took me one sitting of about three hours, and ended up weighing in at just under 100 lines of Common Lisp, not including the package and system definitions.

Utility first:

;; util.lisp
(in-package :forthlike)

(defun println (thing) (format t "~a~%" thing))

(defmacro aif (test if-true if-false)
  `(let ((it ,test))
     (if it ,if-true ,if-false)))

(defmacro bif (test) `(if ,test "true" "false"))

(defmacro with-pop! ((&rest symbols) &body body)
  `(let ,(loop for s in symbols collect `(,s (pop!)))
     ,@body))

(defun parse-num (str)
  (multiple-value-bind (int end) (parse-integer str :junk-allowed t)
    (if (and int (/= end (length str)) (eq #\. (aref str end)))
        (ignore-errors
          (multiple-value-bind (float f-end) (parse-integer str :start (+ end 1))
            (+ int (float (/ float (expt 10 (- f-end end 1)))))))
        int)))

println is a shortcut for printing something with a newline at the end, aif is one of Graham's anaphors, bif is a function to let me deal with the target languages' booleans[3], and with-pop! is a piece of utility to make it easier to work with multiple values from the stack. You'll see how that comes together in a second.

parse-num looks like it's the scariest thing here, but all it actually does is use parse-integer to parse integers or floats.

Moving on...

;; forthlike
(in-package #:forthlike)

(defparameter *stack* nil)
(defparameter *words* (make-hash-table :test #'equal))
(defparameter *input* "")

(defun pull! (&optional (looking-for #\ ))
  (multiple-value-bind (word len) (split-sequence looking-for *input* :count 1)
    (setf *input* (subseq *input* len))
    (first word)))

(defun pop! () (pop *stack*))

(defun push! (thing) (push thing *stack*))

(defun ev (word)
  (if (or (string= "true" word) (string= "false" word))
      (push! word)
      (aif (parse-num word)
           (push! it)
           (aif (gethash word *words*)
                (funcall it)
                (format t "Unknown word: ~s~%" word)))))

(defmacro def (name &body body)
  `(setf (gethash ,name *words*) (lambda () ,@body)))

(def "." (println (pop!)))
(def ".s"
  (println "")
  (if *stack*
      (loop for i from 0 for elem in *stack*
         do (format t "< ~a > :: ~a~%" i elem))
      (format t "< Empty stack >~%"))
  (println ""))

(def "`" (push! (pull!)))
(def "," (funcall (gethash (pop!) *words*)))
(def "\"" (push! (format nil "~s" (pull! "\""))))

(def "dup" (push! (first *stack*)))
(def "swap" (rotatef (first *stack*) (second *stack*)))

(def "+" (push! (+ (pop!) (pop!))))
(def "*" (push! (* (pop!) (pop!))))
(def "/" (with-pop! (b) (push! (/ (pop!) b))))
(def "-" (with-pop! (b) (push! (- (pop!) b))))

(def "=" (push! (bif (equal (pop!) (pop!)))))
(def ">" (push! (bif (with-pop (b) (> (pop!) b)))))
(def "<" (push! (bif (with-pop (b) (< (pop!) b)))))
(def "not" (push! (if (string= (pop!) "false") "true" "false")))
(def "and" (push! (with-pop! (a b) (bif (and (string= "true" a) (string= "true" b))))))
(def "or" (push! (with-pop! (a b) (bif (or (string= "true" a) (string= "true" b))))))
(def "if" (if (string= (pop!) "true")
              (with-pop! (a) (pop!) (ev a))
              (progn (pop!) (ev (pop!)))))

(def ":" (let ((name (pull!))
               (words (loop for wd = (pull!) until (string= wd ";") collect wd)))
           (def name (mapc #'ev words))))

(defun forthlike-eval (str)
  (setf *input* str)
  (loop until (string= *input* "") do (ev (pull!))))

(defun forthlike-load (file-path)
  (with-open-file (s file-path)
    (loop for res = (read-line s nil :eof)
       until (eq res :eof)
         do (forthlike-eval res))))

(defun repl ()
  (loop for line = (progn (format t "~~4th >> ") (read-line)) 
     until (string= line "bye") do (forthlike-eval line)))

And that's all.

(defparameter *stack* nil)
(defparameter *words* (make-hash-table :test #'equal))
(defparameter *input* "")

*stack*, *words* and *input* are storage places for, respectively, the stack, the dictionary, and the current input.

(defun pop! () (pop *stack*))

(defun push! (thing) (push thing *stack*))

(def "dup" (push! (first *stack*)))
(def "swap" (rotatef (first *stack*) (second *stack*)))

(def "+" (push! (+ (pop!) (pop!))))
(def "*" (push! (* (pop!) (pop!))))
(def "/" (with-pop! (b) (push! (/ (pop!) b))))
(def "-" (with-pop! (b) (push! (- (pop!) b))))

pop! and push! are both the obvious stack operations, def is a utility macro to make definitions simpler, and it's immediately used to put together some primitives. The obvious ones are +, *, / and -. . pop!s one thing and prints it, while .s prints the entire stack. There should probably also be a way to print the current dictionary, now that I think about it. dup and swap do exactly what you'd expect, knowing their Forth equivalents.

(def "=" (push! (bif (equal (pop!) (pop!)))))
(def ">" (push! (bif (with-pop (b) (> (pop!) b)))))
(def "<" (push! (bif (with-pop (b) (< (pop!) b)))))
(def "not" (push! (if (string= (pop!) "false") "true" "false")))
(def "and" (push! (with-pop! (a b) (bif (and (string= "true" a) (string= "true" b))))))
(def "or" (push! (with-pop! (a b) (bif (or (string= "true" a) (string= "true" b))))))
(def "if" (if (string= (pop!) "true")
              (with-pop! (a) (pop!) (ev a))
              (progn (pop!) (ev (pop!)))))

The boolean functions all operate on the symbols true and false, represented here as strings. Those symbols include =, >, <, not, and, or and if. The reason I'm not sure this is the best way to handle it is that it makes true and false pretty glaring exceptions to the basic rules of the language. Ideally, I'd have some way of designating a class of words that self-evaluate, and let the user play with them too. This is something I'm thinking about for an upcoming article, though I guess it's possible that I'm just taking it too seriously. Anyhow.

Ok, here's where this gets interesting.

(defun pull! (&optional (looking-for #\ ))
  (multiple-value-bind (word len) (split-sequence looking-for *input* :count 1)
    (setf *input* (subseq *input* len))
    (first word)))

pull! grabs the next "word" from *input*. By default, that's the next space-delimited chunklet, but it's possible to change the terminating character. This turns out to be fairly useful for things like ", which looks for the next quote[4].

(def "`" (push! (pull!)))
(def "," (funcall (gethash (pop!) *words*)))
(def "\"" (push! (format nil "~s" (pull! "\""))))

...

(def ":" (let ((name (pull!))
               (words (loop for wd = (pull!) until (string= wd ";") collect wd)))
           (def name (mapc #'ev words))))

pull! is used in places where we care about upcoming input, and it lets Forthlike define : as merely looking for the word ;, rather than something more complicated. It also lets me define two words that exert some control of evaluation. ` calls pull!, and pushes the result onto the stack without calling ev on it, while , calls pop! and tries to treat the result as a function to call. I was tempted to just make it call ev, but I'm not too sure that would be the best idea since numbers and symbols would just stay on the stack.

The evaluation conditions and evaluation time could both use a pretty thorough thinking session; would it be ok to tokenize things as they're pulled? That is, parse numbers, intern symbols in the keywords package, and intern/lookup the functions? That would mean that it would be easier to tell what to do with the thing on top of the stack; strings, keywords and numbers get left there and functions get called. Do I want to look up functions right away? Or should I keep their name on the stack? What are the implications of that? Do I want to re-think the *words* table entirely? For example, by making : create a lambda rather interning a function, and then letting a different function designate names in the *words* table? That would make it pretty easy to define variables too, which the system currently lacks.

(defun forthlike-eval (str)
  (setf *input* str)
  (loop until (string= *input* "") do (ev (pull!))))

(defun forthlike-load (file-path)
  (with-open-file (s file-path)
    (loop for res = (read-line s nil :eof)
       until (eq res :eof)
         do (forthlike-eval res))))

(defun repl ()
  (loop for line = (progn (format t "~~4th >> ") (read-line)) 
     until (string= line "bye") do (forthlike-eval line)))

The last three functions are what actually let you use the language. forthlike-eval takes a string and evaluates it one word at a time, forthlike-load uses forthlike-eval to load named files, and repl uses forthlike-eval in conjunction with read-line to make a Forthlike REPL available.

It's a pretty featureful little toy for three hours of work. I may come back to this at some point in the future.


Footnotes

1 - [back] - As well as a replacement keycap for your Caps Lock, if you go that route.

2 - [back] - Though using Lisp to implement something not unlike Forth feels a little bit like cheating.

3 - [back] - Though I'm not convinced I took the right approach quite yet.

4 - [back] - It doesn't take escapes into account yet, though I don't suspect that would be very difficult to add. Likewise, it would be nice if I could designate a character to nest on, so that we could grab balanced expressions. Things for the future, I'm sure.

Thursday, August 1, 2013

REBOL Mode

I need a short break here. It's nowhere near done yet, not even the pieces I wanted to put together. But, at the risk of ending up with another piece of detritus littering my blog, I need to let off some steam and talk about where I'm going with this.

For the past couple of days, I've been busy working on writing a replacement for rebol.el and running into some not altogether unexpected headaches. The file I just linked you hasn't been updated since about 2001, and doesn't include a license block. After attempting to contact its current host and getting no response, I just went ahead and started from scratch. I had a few goals from the outset:

Proper Highlighting

The current rebol.el was put together for REBOL2, and thus lacks highlighting for certain symbols that have been introduced since. The one that sticks out most in my mind is the symbol funct, which you saw semi-humorously higlighted as funct in the third section last time.

Jump-To-Definition

Some kind of binding in a mode that lets you jump to the file and line of the definition of a given symbol. Not entirely sure what the interaction there is going to be, probably just a key-binding that jumps for the thing-at-point. This one looks like it would be pretty simple to pull off actually; when a file is loaded, record the position of any assignments in it. Assignments are simple to find, since there's exactly one way to do it, and it involves adding a single-character suffix to whatever word you're assigning.

REPL

There isn't a run-rebol, in the style of run-python or run-lisp, and I'd like one.

Send Region

Fairly self-explanatory. Or maybe not? In Lisp modes, there's typically a binding to evaluate the current s-expression, either C-c C-c or C-M-x. When you hit it, the effect is to evaluate the surrounding block into the REPL. There isn't a send-region command in the current rebol-mode, probably because they don't directly implement an in-Emacs-REPL, but since I want the second, I'd also like the first.

Documentation Display

Just a simple, straight-forward way to display help about a particular symbol in a separate buffer. Nothing fancy, move along. Ok, in a future edition, it would be nice if the return text was all linkified and highlighted so that you could click/<Ret> through docs, but that can wait.

Source Display

This one might be a bit more functional. You see, you can use the source function to get a source dump of almost[1] any REBOL3 word. It may or may not be useful at all, but it would be pretty cool to build a buffer that would let you load such source output, change it, then send it back to the REPL when you save.

Argument Hints

If you've used things like SLIME, you'll appreciate this one. As you're typing, a summary of the arguments to the thing you're typing shows up in the minibuffer. This is trivial in Lisp, because of the way everything is parenthesized pretty consistently. It turns out to be quite a headache in REBOL3, and basically necessitates interacting with some sort of running runtime system. Here's an example, pretend these are all actual REBOL words:

foo bar baz mumble |

Assuming that pipe represents my cursor, what should the mode display in your minibuffer, and how would you find out? Near as I can tell, you'd need to ask a running r3 interpreter with the words foo, bar, baz and mumble defined. What it would do is:

  • check if mumble is a function, and if so, print the arg-hint for mumble, otherwise
  • check if baz is a function of more than one argument, and if so print the arg-hint for baz, otherwise
  • check if bar is a function of more than two arguments, and if so print the blah blah blah

until you run out of words to check. Another open question is: how far back should the mode look for relevant symbols? For the moment, I've settled on "To the beginning of the previous block, or the first assignment, whichever comes first", but that's probably not the best approach to take.

Where I've Got So Far

At the moment, I'm about a quarter of the way there by my reckoning. And I've run into some issues, both expected and unexpected. The mode as currently posted here, implements proper highlighting, a basic REPL, a basic documentation display, a basic source display, and a hacked-together send-region. I've already gone through the problems with argument hinting in an almost-purely whitespace-delimited language; there was only one completely unexpected problem and two little gotchas I ran into. Lets start small:

Gotcha the first is that REBOL path strings aren't fully cross-platform. They do the standard Unix thing, and auto-convert for Windows, but if you include a drive letter, which the Windows version of Emacs does by default, your string won't be recognized as a file. As a result, I need that extra snippet to sanitize Windows paths.

Gotcha the second is another cross-platform, or possibly cross-version, issue. For some reason the Linux edition of the r3 comint buffer prints its input before its return value. That is

(defun proc-filter (process msg)
  (message "%s" msg))

(set-process-filter proc #'proc-filter)

;; on Linux

(process-send-string proc "source source")

;; Output to *Message* is
;;
;;    source source
;;    source: make function ! [[ 
;;    ..
;;    >>

;; on Windows

(process-send-string proc "source source")

;; Output to *Message* is
;;
;;    source: make function ! [[ 
;;    ..
;;    >>

Not a huge deal, except that I have to deal with it if I want to succeed in my master plan of running an r3 interpreter behind the scenes. Which brings me to the big, unexpected piece of code I had to write. This actually took a few tries, as I came to grips with the situation.

(defun r3-process-filter (proc msg)
  "Receives messages from the r3 background process.
Processes might send responses in 'bunches', rather than one complete response,
which is why we need to collect them, then split on an ending flag of some sort.
Currently, that's the REPL prompt '^>> '"
  (let ((buf ""))
    (setf buf (concat buf msg))
    (when (string-match ">> $" msg)
      (mapc #'r3-ide-directive 
            (split-string buf "^>> "))
      (setf buf ""))))

(defun r3-send! (string)
  "Shortcut function to send a message to the background r3 interpreter process"
  (process-send-string r3-rebol-process (concat string "\n")))

(set-process-filter r3-rebol-process #'r3-process-filter)

(defun r3-ide-directive (msg)
  (let* ((raw-lines (butlast (split-string msg "\r?\n")))
         ;; the linux edition seems to return the function call before its output. Might also be an Emacs version issue.
         (lines (if (eq system-type 'gnu/linux) (rest raw-lines) raw-lines)))
    (when lines
      (cond ((string-match "NEW-KEYWORDS: \\(.*\\)" (first lines))
             (let ((type (intern (match-string 1 (first lines)))))
               (setf (gethash type r3-highlight-symbols) (rest lines))
               (r3-set-fonts)))
            ((string-match "HELP: \\(.*\\)" (first lines))
             (get-buffer-create "*r3-help*")
             (with-current-buffer "*r3-help*"
               (kill-region (point-min) (point-max))
               (insert ";;; " (match-string 1 (first lines)) " ;;;\n\n")
               (mapc (lambda (l) (insert l) (insert "\n")) (rest lines)))
             (pop-to-buffer "*r3-help*"))
            ((string-match "SOURCE" (first lines))
             (ignore-errors (kill-buffer "*r3-source*"))
             (get-buffer-create "*r3-source*")
             (with-current-buffer "*r3-source*"
               (mapc (lambda (l) (insert l) (insert "\n")) (rest lines))
               (r3-mode))
             (pop-to-buffer "*r3-source*"))))))

The third piece there isn't terribly important[2]. The gist of it is that I want to run a separate r3 process, and communicate it for certain things. In order to do that, I have to attach a listener to the process. Then, whenever I send a string to the process, it will respond with a process id and message to that listener.

The catch I wasn't counting on was that output arrives in "bunches". Which is to say, if you send three or four commands, you're going to get back strings of ~400 characters, each containing either a partial response, a full response or multiple full/partial responses. Because I'm not expecting responses much larger than a couple thousand characters, I can get away with just buffering until output lets up, but that might not be the best general strategy.

I'll talk about this a bit more after I've had some more time to work on it. Right now?

I. Need. Sleep.

Cheers.


Footnotes

1 - [back] - Before you ask, yes, it's entirely possible to get the source of source. The only words you can't introspect on in this way are native!s, which are implemented in C rather than REBOL.

2 - [back] - As a note to self, I'm going to have to re-write pieces of it. Both for speed, and because I'm repeating blocks for each condition. That needs to be a mini-dsl instead of manual code.