summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--crabbes-corner.org2
-rw-r--r--mafia.org660
-rw-r--r--server.lisp12
-rw-r--r--wink-murder.el142
4 files changed, 816 insertions, 0 deletions
diff --git a/crabbes-corner.org b/crabbes-corner.org
new file mode 100644
index 0000000..92f8dac
--- /dev/null
+++ b/crabbes-corner.org
@@ -0,0 +1,2 @@
+* english villiage simulator
+https://archaeology.co.uk/articles/specials/timeline/the-origins-of-the-english-village.htm
diff --git a/mafia.org b/mafia.org
new file mode 100644
index 0000000..73a1b1b
--- /dev/null
+++ b/mafia.org
@@ -0,0 +1,660 @@
+* Building a Murder Mystery Game Prototype
+** Summary
+
+Ideally we would like to create a small city/village simulator where there
+are many independent actors all doing their routines. One of the actors gets
+triggered by something and commits a murder. Then the player acts as detective,
+talking to other actors and gaining clues to solve who-done-it.
+
+This document serves as a tutorial for Emacs, Lisp and org-mode's literate
+programming features. It provides a way to distribute the notes, code, and
+execution environment all in one place. Anyone reading this document can also
+edit and execute the code in it. This is the beauty of literate programs, where
+the program is written for humans first as prose with code embedded.
+
+** Wink Murder - Boiling It Down
+
+the game [[https://en.wikipedia.org/wiki/Wink_murder]["Wink Murder"]] is
+a very simplified murder mystery and serves as a starting point to work
+out a prototype. The actors are all observing one another and the killer must
+try to wink at as many of the innocents as they can before being accused and
+caught. This will be a pure simulation, where we can learn about creating
+actor behavior representing knowledge. Does the killer think they're being watched?
+Did one of the innocents notice them wink? How can we encode some of these
+behaviors into a simulated version of people sitting in a circle and playing
+this game?
+
+* Program Overview
+
+the following source block represents the whole program from a high level.
+its like a table of contents, where each of the =<<name>>= blocks actually
+points to other source code blocks in this document. The header argument
+~:noweb yes~ tells org-mode to unfold the references into code, so when
+it sees =<<dependencies>>=, it will insert the code from the block with that
+name. The header argument ~:tangle yes~ means we can evaluate
+~(org-babel-tangle)~ and it will unfold all of the code references into a
+source file. This is the core of literate programming.
+
+#+name: wink-murder
+#+begin_src emacs-lisp :noweb yes :tangle yes :results silent
+ ;;; wink-murder.el --- Emacs Wink-Murder game simulation -*- lexical-binding:t -*-
+
+ <<dependencies>>
+
+ <<wink-murder-class>>
+
+ <<actor-classes>>
+
+ <<initialization-helpers>>
+
+ <<top-level-game-functions>>
+
+ <<actor-behavior-methods>>
+
+ <<game-loop>>
+#+end_src
+
+If you put your cursor on the block above and press C-c C-c, Emacs will
+ask if you want to evaluate the code on your system. This is a good thing,
+since you are executing most of the elisp in this file without looking
+at it! You can set a variable to allow it to execute automatically, but
+its nice to have the safety on.
+
+#+begin_src emacs-lisp
+(setq org-confirm-babel-evaluate nil)
+#+end_src
+
+Now you should be able to press M-x wink-murder-play and it will prompt you for
+a number of players. Enter 4 (lower) will. Then look at the *Messages*
+buffer, you can either find it through the menu bar, ~M-x switch-to-buffer~
+or C-c C-c the source block below:
+
+#+begin_src emacs-lisp
+(switch-to-buffer "*Messages*")
+#+end_src
+
+** dependencies
+
+i'm going to bring in some dependencies that will make it more like Common
+Lisp. [[info:cl#Top][cl-lib]] brings in functions and macros. When you see things prefixed with
+~cl-~, you'll know its from Common Lisp. [[info:eieio#Top][EIEIO]] provides an OOP layer similar to
+CLOS, the powerful object oriented system from CL.
+
+#+name: dependencies
+#+begin_src emacs-lisp :results silent
+ (require 'cl-lib)
+ (require 'eieio)
+#+end_src
+
+* Game State
+
+a game consists of N >= 4 *actors*, one of which is the *killer*. each game will
+have a number of *rounds*, at the end of each an actor will /die/. each round
+must simulate time in some way. each *tick*, an actor /observes/ their
+fellows. the killer will /wink/ at another actor when they happen to be observing
+each other. after a *delay* of χ ticks, the winked-at actor dies and the round
+ends. once per round, each actor may /accuse/ another of being the killer.
+then the group attemps to reach /consensus/ on this accusation. if they do, the
+other actor reveals whether or not they are the killer. (Q: what makes the killer
+join the consensus against themself?) If they are the killer, the other actors
+win. If there's only 2 players left, the killer wins.
+
+** Game class ~wink-murder~
+using EIEIO, lets define a class ~wink-murder~ to represent the whole game state.
+
+#+name: wink-murder-class
+#+begin_src emacs-lisp :results silent
+ (defclass wink-murder () ; No superclasses
+ ((actors :initarg :actors
+ :initform (wink-murder-initialize-actors 4)
+ :type list
+ :documentation "The list of `actors' in the game.")
+ (round :initform 1
+ :type number
+ :documentation "The current round of the game.")
+ (tick :initform 0
+ :type number
+ :documentation "The current 'slice-of-time' the game is in.")
+ (events :initform nil
+ :type list
+ :documentation "List of events in the game's timeline."))
+ "A class representing the game state of Wink-Murder, defaults to 4 players.")q
+#+end_src
+
+Notice the ~:initform~ slot options (instance variables are called slots in
+CLOS/EIEIO). By default, ~(make-instance 'wink-murder)~ would initialize the object
+instance with these values. We will work on defining ~wink-murder-initialize-actors~ next.
+
+** Actors
+
+We may as well use an object to represent the actors as well. Each one will have
+an *id* and a *status* which will be one of ~'alive 'dead 'killer~. We can actually
+use inheritance here to set apart the killer with its own ~:initform~.
+
+#+name: actor-classes
+#+begin_src emacs-lisp :results silent
+ (defclass wink-murder-actor ()
+ ((id
+ :initarg :id
+ :type number
+ :reader wink-murder-actor-id)
+ (target
+ :initarg :target
+ :documentation "Actor currently being observed."
+ :accessor wink-murder-actor-target)
+ (status
+ :initform 'alive
+ :documentation "'alive, 'dying, or 'dead")
+ (notes
+ :initform '()
+ :documentation "An alist containing pairs of (actor-id . target-id)"))
+ "Base class for wink-murder actors.")
+
+ (defclass wink-murder-killer (wink-murder-actor)
+ ()
+ "Actor subclass to represent the killer.")
+
+ (defclass wink-murder-innocent (wink-murder-actor)
+ ((death-countdown
+ :initform (1+ (random 10))
+ :documentation "The number of ticks to go from dying to dead")))
+#+end_src
+
+Then the function ~wink-murder-initial-actors~ will handle initializing N actors
+into a list which is the ~:initform~ of the ~wink-murder~ game instance.
+
+** Game Initialization Functions
+
+#+name: initialization-helpers
+#+begin_src emacs-lisp :results silent
+ (defun wink-murder-initialize-actors (players)
+ "Returns a list of `players' wink-murder-actors, where one is the killer."
+ (cl-assert (>= players 4) () "Cannot play with fewer than 4 players")
+ (let* ((killer (1+ (random players)))
+ (actors (cl-loop for i from 1 to players
+ collect (if (eql i killer) (wink-murder-killer :id i) (wink-murder-innocent :id i)))))
+ (mapc (lambda (a)
+ (setf (wink-murder-actor-target a) (wink-murder-random-other a actors)))
+ actors)))
+#+end_src
+
+** visualizing initial game state
+
+Lets initialize a game with 6 actors and inspect it to see what to expect.
+
+#+begin_src emacs-lisp
+ (let* ((wink-murder-game (wink-murder :actors (wink-murder-initialize-actors 6)))
+ (actors (slot-value wink-murder-game 'actors)))
+ (cons '(class id status) ;; add the header row
+ (mapcar (lambda (a)
+ (let ((class (eieio-object-class a)))
+ (with-slots (id status) a
+ (list class id (when (eql class 'wink-murder-innocent) status)))))
+ actors)))
+#+end_src
+
+* Basic Game Loop
+
+The game loop will advance by a single tick where each actor /observes/ the others.
+So... we need to define a game loop function, and a method for the actors to
+
+#+name: game-loop
+#+begin_src emacs-lisp :results silent
+ (defun wink-murder-play (players)
+ "Entry point to start a game of Wink-Murder."
+ (interactive "nnumber of players: ")
+ (with-current-buffer "*WINK-MURDER-LOG*" (erase-buffer))
+ (setq wink-murder-active-game (wink-murder :actors (wink-murder-initialize-actors players)))
+ (while (> (length (wink-murder-living-innocents wink-murder-active-game)) 1)
+ (wink-murder-update wink-murder-active-game))
+ (mapc #'wink-murder-log-event (reverse (slot-value wink-murder-active-game 'events)))
+ (switch-to-buffer "*WINK-MURDER-LOG*"))
+#+end_src
+
+* Top level game functions
+
+Now that i think of it, using functions here would be simpler. Its likely faster,
+and is definitely in Common Lisp. Unless we want to dispatch or use method chains,
+there is not reason to define methods a la Ruby.
+
+#+name: top-level-wink-murder-functions
+#+begin_src emacs-lisp :results silent
+ (defun wink-murder-living-innocents (game)
+ "Returns the living innocents from a wink-murder game."
+ (cl-remove-if-not #'wink-murder-alive-p (wink-murder-innocents game)))
+
+ (defun wink-murder-update (game)
+ "Performs the update logic for the wink-murder game instance."
+ (with-slots (actors tick) game
+ (setf tick (1+ tick))
+ (mapc 'wink-murder-observe actors)))
+
+ (defun wink-murder-innocents (game)
+ "Returns the list of innocents from a wink-murder game."
+ (cl-remove-if #'wink-murder-killer-p (slot-value game 'actors)))
+
+ (defun wink-murder-current-tick ()
+ (slot-value wink-murder-active-game 'tick))
+
+ (defun wink-murder-add-event (event)
+ (object-add-to-list wink-murder-active-game 'events event))
+#+end_src
+
+* Actor Behavior
+** Observation
+:PROPERTIES:
+:header-args: :noweb-ref actor-behavior-methods :noweb-sep "\n\n" :results silent
+:END:
+
+Each actor will have a ~target~, another actor they are observing.
+While they are observing, they'll notice who their target is observing.
+If two actors are observing each other, they have *eye-contact*. The killer
+will wink if they believe they aren't ~being-watched?~ when eye contact
+is being made.
+
+We'll implement a base method for all actors that can be called after more
+specialized methods. This base method will be responsible for the actors'
+"memory", adding a note about who they're observing is observing. Perhaps
+later on it will be "fuzzy."
+
+#+name: observe-base
+#+begin_src emacs-lisp :results silent
+ (cl-defmethod wink-murder-observe ((actor wink-murder-actor))
+ "Base behavior for an actor. Note the ids of the observed target and who
+ they are perceived to be targeting."
+ (with-slots (notes (my-target target)) actor
+ (when my-target
+ (with-slots (id (their-target target)) my-target
+ (when their-target
+ (setf notes (cons `(,id . ,(wink-murder-actor-id their-target)) notes)))))))
+#+end_src
+
+For now, we just need to give the innocents random chance to target a
+new person. Otherwise, the sim will go into an endless loop as the killer
+will never make eye contact.
+
+#+name: observe-innocent
+#+begin_src emacs-lisp
+ (cl-defmethod wink-murder-observe ((actor wink-murder-innocent))
+ (when (> 5 (random 11))
+ (with-slots (id target) actor
+ (let* ((new-target (wink-murder-random-other actor (slot-value wink-murder-active-game 'actors)))
+ (new-id (wink-murder-actor-id new-target))
+ (new-status (slot-value new-target 'status)))
+ (wink-murder-add-event
+ (wink-murder-retarget-event :actor-id id :old (wink-murder-actor-id target) :new new-id
+ :message (format "Innocent %d observes %d and sees they are %s" id
+ new-id new-status)))
+ (setf target new-target))))
+ (cl-call-next-method))
+#+end_src
+
+We may not have to specialize the other actors, but while the killer is
+observing, they will decide whether or not to wink. But first we'll need
+a method to determine eye-contact and one for the killer to determine if
+they're being watched.
+
+#+name: eye-contact?
+#+begin_src emacs-lisp
+ (defun wink-murder-eye-contact? (a b)
+ "Given two `wink-murder-actor's, returns t if they are eachother's current target."
+ (and (equal (slot-value a 'target) b)
+ (equal (slot-value b 'target) a)))
+#+end_src
+
+Eye contact is pretty straight forward, but ~being-watched?~ needs to utilize
+the *notes* "memory" from above. For now, we'll look at the first element in
+the list and see if the target is the killer.
+
+#+name: neighbors
+#+begin_src emacs-lisp
+ (defun neighbors (e lst)
+ (let* ((idx (cl-position e lst))
+ (len (length lst))
+ (left (elt lst (mod (1- idx) len)))
+ (right (elt lst (mod (1+ idx) len))))
+
+ (list left right)))
+#+end_src
+
+#+name: being-watched?
+#+begin_src emacs-lisp
+ (cl-defmethod wink-murder-being-watched? ((killer wink-murder-killer))
+ "Specilized on the killer, returns true when there is a most recent memory,
+ and the target is the killer themselves."
+
+ ;; (with-slots (id notes) killer
+ ;; (let* ((most-recent-memory (car notes))
+ ;; (their-target (cdr most-recent-memory)))
+ ;; (and their-target (= id their-target))))
+
+ (> 5 (random 11))
+ )
+#+end_src
+
+If they're being watched, simply have them target a random other actor (?)
+
+#+name: wink-murder-observe-killer
+#+begin_src emacs-lisp :results silent
+ (cl-defmethod wink-murder-observe ((killer wink-murder-killer))
+ "Specialized behavior for the `wink-murder-killer'."
+ (with-slots (id target) killer
+ (with-slots ((old-id id)) target
+ (if (wink-murder-being-watched? killer)
+ (let* ((new-target (wink-murder-random-other killer (wink-murder-living-innocents wink-murder-active-game)))
+ (new-id (wink-murder-actor-id new-target)))
+ (wink-murder-add-event
+ (wink-murder-retarget-event :actor-id id :old old-id :new new-id
+ :message (format "the killer targets %d" new-id)))
+ (setf target new-target))
+ (when (wink-murder-eye-contact? killer target)
+ (progn
+ (wink-murder-add-event
+ (wink-murder-event :actor-id id :message (format "the killer winks at %d." old-id)))
+ (wink-murder-innocent-die target)))
+ (cl-call-next-method killer)))))
+#+end_src
+
+** Selecting a random other actor
+
+#+name: wink-murder-random-other
+#+begin_src emacs-lisp
+ (defun wink-murder-random-other (actor other-actors)
+ (with-slots (id) actor
+ (let ((other-ids (cl-remove-if (lambda (i) (= i id))
+ (mapcar 'wink-murder-actor-id other-actors))))
+ (cdr (object-assoc (seq-random-elt other-ids) :id other-actors)))))
+#+end_src
+
+#+begin_src emacs-lisp
+ (let* ((game (wink-murder :actors (wink-murder-initialize-actors 15)))
+ (actor (cl-first (slot-value game 'actors))))
+ ;; (cl-loop for i upto 10
+ ;; collect (list (wink-murder-random-other actor (slot-value game 'actors))))
+ (wink-murder-random-other actor (slot-value game 'actors))
+ )
+#+end_src
+
+** TODO Example Three Actor Play
+:PROPERTIES:
+:header-args: :noweb-ref example-three-way-setup
+:END:
+
+*NOTE* code example here is currently "broken" due to random behavior in newer
+code
+
+Imagining "optimal" play if there are only 3 actors. The game begins and
+each actor chooses a target. If the killer makes eye contact with anyone,
+they'll wink, no matter if they're being observed or not, since they win
+the game. If the other two make eye contact, they will never want to
+observe the other player, because then they'll be killed. One of the two
+would /accuse/ and the other would /second/ and they win.
+
+Let's set this up. We'll need a killer with no target, and two innocents,
+~marple~ the killer and ~poirot~ targets the her.
+
+~let*~ sets some local variables for a block. latter definitions can refer
+to variables created previously.
+
+#+begin_src emacs-lisp
+ (let* ((killer (wink-murder-killer :id 1))
+ (marple (wink-murder-innocent :id 2 :target killer))
+ (poirot (wink-murder-innocent :id 3 :target marple)))
+#+end_src
+
+Then, set the killer's target to ~poirot~ :
+
+#+begin_src emacs-lisp
+ (setf (slot-value killer 'target) poirot)
+#+end_src
+
+The killer observes:
+
+#+begin_src emacs-lisp
+ (wink-murder-observe killer)
+#+end_src
+
+Then change target and observe again:
+
+#+begin_src emacs-lisp
+ (setf (slot-value killer 'target) marple)
+ (wink-murder-observe killer)) ;; end let*
+#+end_src
+
+~C-c C-c~ on the following block will run this code:
+
+#+begin_src emacs-lisp :noweb yes :noweb-ref none :tangle no
+ <<example-three-way-setup>>
+ (with-current-buffer "*WINK-MURDER-LOG*" (buffer-string))
+#+end_src
+
+Add in a 4th actor, and then its trickier. The killer would like to wink
+when they are sure they aren't being watched and then immediately try for
+eye contact with another actor. The other actors may want to maintain
+eye contact as long as they feel the actor they are observing is being
+watched by someone else. ???
+
+** Unfinished Targeting behavior
+
+#+begin_src emacs-lisp
+
+ (cl-defgeneric wink-murder-maybe-refocus (actor)
+ "Actor decides to maintain observation target or pick another.")
+
+ (cl-defmethod wink-murder-maybe-refocus ((actor wink-murder-actor) other-actors)
+ (when (wink-murder-refocus? actor)
+ (wink-murder-refocus actor other-actors)))
+
+ (cl-defmethod wink-murder-refocus? ((actor wink-murder-killer))
+ (slot-value actor 'being-watched?))
+
+ (cl-defmethod wink-murder-refocus ((actor) other-actors)
+ (with-slots ((target) actor)
+ (setf target (seq-random-elt other-actors))))
+#+end_src
+
+** ~wink-murder-alive-p~ actor predicate
+:PROPERTIES:
+:header-args: :noweb-ref actor-behavior-methods :noweb-sep "\n\n" :results silent
+:END:
+
+#+begin_src emacs-lisp
+ (defun wink-murder-alive-p (actor)
+ "Returns `t' if the actor is alive, otherwise `nil'"
+ (eql (slot-value actor 'status) 'alive))
+#+end_src
+
+** Dying Actors
+:PROPERTIES:
+:header-args: :noweb-ref actor-behavior-methods :noweb-sep "\n\n" :results silent
+:END:
+
+We need a method to make an actor die. For now, we'll just print some
+message and update its state so that the ~alive~ slot is ~nil~. According
+to the game rules, we should start some "timer" so that it will count down
+its ~death-countown~, but I'm not quite prepared for that at this moment.
+
+#+begin_src emacs-lisp
+ (defun wink-murder-innocent-die (actor)
+ (with-slots (id status) actor
+ (wink-murder-add-event (wink-murder-event :actor-id id :message "AIIEEEE!!"))
+ (setf status 'dead)))
+#+end_src
+
+* Events
+** Summary
+
+Rather than logging every single thing that happens in the sim, perhaps we can
+emit Events when something significant happens. As devs wanting to inspec the
+simulation, it might be nice to see every action one of the actors takes. Thus,
+we can emit an event when an actor changes targets, but don't have to do anything
+if they keep looking at the same one.
+
+Its relatively the same to how the log function in the code (as i write this)
+is only logging when the killer winks, someone dies, or target switches.
+
+But this is data! It makes up the timeline of the simulation, and one list of
+events can describe a whole game. It could be visualized by stepping through it
+or perhaps showing it all laid out as one with certain events highlighted.
+
+Giving some structure to this fact rather than just logging it into a buffer
+gives us some more flexibility to displaying it down the road.
+
+So we should ad a slot to ~wink-murder-game~ to be a list of ~wink-murder-event~ objects.
+Each event could have a reference to the actor who caused it, the current ~tick~
+or ~round~ when it happened (gotta clear up this time model), and some message
+or other data. Specializing event types could allow us to use some generic
+function like ~wink-murder-display-event~ and each type could use the base behavior or
+something more specialized as needed.
+
+** ~wink-murder-event~ classes
+
+#+name: wink-murder-event-class
+#+begin_src emacs-lisp
+ (defclass wink-murder-event nil
+ ((tick
+ :initform (wink-murder-current-tick)
+ :custom number
+ :label "Time of occurance"
+ :documentation "The tick of the parent game when the event happened")
+ (actor-id
+ :initarg :actor-id
+ :custom number
+ :label "Actor ID"
+ :documentation "The id of the actor who caused event.")
+ (message
+ :initarg :message
+ :custom string
+ :label "Event message"
+ :documentation "Freeform text string for an event message"))
+ "Base class for events that happen during a wink-murder simulation.")
+
+ (defclass wink-murder-retarget-event (wink-murder-event)
+ ((old
+ :initarg :old
+ :custom number
+ :label "ID of previous target")
+ (new
+ :initarg :new
+ :custom number
+ :label "ID of new target")))
+#+end_src
+
+#+RESULTS: wink-murder-event-class
+: wink-murder-retarget-event
+
+** ~wink-murder-event-log~ methods
+
+The base method handles formatting the log string and sticking in all the relevant
+data from the event object. The ~&rest extra~ in the argument list lets this method
+take an unspecified number of optional extra parameters. We can pass down additional
+pre-formatted strings from specialized methods and log all of those with
+~(apply #'wink-murder-log extra-strings)~. The log string will look something like this
+(subject to change):
+
+ =000389: wink-murder-event actor 3 --- msg: pooop=
+
+#+name: base-wink-murder-log-event
+#+begin_src emacs-lisp
+ (cl-defmethod wink-murder-log-event ((event wink-murder-event) &rest extra-strings)
+ (with-slots (tick actor-id message) event
+ (let ((format-string "%06d: %s actor %d --- msg: %s")
+ (event-type (eieio-object-class event)))
+ (wink-murder-log format-string tick event-type actor-id
+ (propertize message 'face 'font-lock-string-face))
+ (when extra-strings (apply #'wink-murder-log extra-strings)))))
+#+end_src
+
+Lets specialize for the retarget event class, and we can ~cl-call-next-method~
+to pass control to the base ~wink-murder-log-event~ method.
+
+#+name: retarget-wink-murder-log-event
+#+begin_src emacs-lisp
+ (cl-defmethod wink-murder-log-event ((event wink-murder-retarget-event))
+ (with-slots (actor-id old new) event
+ (cl-call-next-method event (format "%02d focuses from %02d to %02d" actor-id old new))))
+#+end_src
+
+#+begin_src emacs-lisp
+ (wink-murder-log-event
+ (wink-murder-retarget-event
+ :actor-id 3 :message "foo" :old 2 :new 8))
+#+end_src
+
+* Emacs "UI"
+
+we can use an emacs buffer and all of the ways we have to manipulate text to
+display the simulation.
+
+** ~wink-murder-log~
+
+For now, we'll just make a log buffer so we can print "debug" messages
+to it as the game progresses.
+
+#+begin_src emacs-lisp
+ (defvar wink-murder-log-buffer "*WINK-MURDER-LOG*"
+ "Insert text here with the `wink-murder-log' function.")
+#+end_src
+
+borrowing a logging defun from [[info:emms#Top][EMMS]] :
+
+#+begin_src emacs-lisp
+ (defun wink-murder-log (&rest args)
+ (with-current-buffer (get-buffer-create wink-murder-log-buffer)
+ (goto-char (point-max))
+ (insert (apply #'format args) "\n")))
+#+end_src
+
+~with-current-buffer~ temporarily sets the "current buffer" for all basic text
+operations. here we're using the buffer variable declared above, going to the
+end of it with ~point-max~ and inserting whatever ~(apply #'format args)~ is.
+
+Let's see...
+
+#+begin_src emacs-lisp
+ (apply #'format (list "foo %s %s" "bar" "baz"))
+#+end_src
+
+#+RESULTS:
+: foo bar baz
+
+Ah ok, we can pack up data for a ~format~ string into a list and print whatever.
+
+** Inspecting/Manipulating Individual Actors
+
+EIEIO has facilites to hook into the Emacs Custom / Widget apis if you add
+correct properties to the class definition. For example:
+
+#+begin_src emacs-lisp
+ (require 'eieio-custom)
+
+ (defclass my-foo nil
+ ((a-string :initarg :a-string
+ :initform "Thunderous pop!"
+ :custom string
+ :label "Amorphous String"
+ :group (default foo)
+ :documentation "A string for testing custom.
+ This is the next line of documentation. It will be folded up
+ in the 'UI'.")
+ (listostuff :initarg :listostuff
+ :initform ("1" "2" "3")
+ :type list
+ :custom (repeat (string :tag "Stuff"))
+ :label "List of Strings"
+ :group foo
+ :documentation "A list of stuff."))
+ "A class for testing the widget on.")
+
+ (eieio-customize-object (my-foo))
+#+end_src
+
+This is Emacs specific, but can leverage the powerful text interface already provided.
+You can extend the methods for editing and displaying the objects, so it could be used
+while paused for inspecting and tweaking the state of anything in the simulation.
+
+However, this and the log above make me think that we also need things we can detect as
+the simulation runs. Something like ~wink-murder-event~ objects that build a *timeline* on the
+game. The high level view would be focused on the timeline, rather than what an individual
+actor is doing at any given time.
+
diff --git a/server.lisp b/server.lisp
new file mode 100644
index 0000000..6660e1b
--- /dev/null
+++ b/server.lisp
@@ -0,0 +1,12 @@
+(defun create-server (port)
+ (let* ((socket (usocket:socket-listen "127.0.0.1" port))
+ (connection (usocket:socket-accept socket :element-type 'character)))
+ (unwind-protect
+ (princ "here")
+ (progn
+ (format (usocket:socket-stream connection) "Hello World~%")
+ (force-output (usocket:socket-stream connection)))
+ (progn
+ (format t "Closing sockets~%")
+ (usocket:socket-close connection)
+ (usocket:socket-close socket)))))
diff --git a/wink-murder.el b/wink-murder.el
new file mode 100644
index 0000000..46d2bd6
--- /dev/null
+++ b/wink-murder.el
@@ -0,0 +1,142 @@
+;;; wink-murder.el --- Emacs Wink-Murder game simulation -*- lexical-binding:t -*-
+
+(require 'cl-lib)
+(require 'eieio)
+
+(defclass wink-murder () ; No superclasses
+ ((actors :initarg :actors
+ :initform (wink-murder-initialize-actors 4)
+ :type list
+ :documentation "The list of `actors' in the game.")
+ (round :initform 1
+ :type number
+ :documentation "The current round of the game.")
+ (tick :initform 0
+ :type number
+ :documentation "The current 'slice-of-time' the game is in.")
+ (events :initform nil
+ :type list
+ :documentation "List of events in the game's timeline."))
+ "A class representing the game state of Wink-Murder, defaults to 4 players.")
+
+(defclass wink-murder-actor ()
+ ((id
+ :initarg :id
+ :type number
+ :reader wink-murder-actor-id)
+ (target
+ :initarg :target
+ :documentation "Actor currently being observed."
+ :accessor wink-murder-actor-target)
+ (status
+ :initform 'alive
+ :documentation "'alive, 'dying, or 'dead")
+ (notes
+ :initform '()
+ :documentation "An alist containing pairs of (actor-id . target-id)"))
+ "Base class for wink-murder actors.")
+
+(defclass wink-murder-killer (wink-murder-actor)
+ ()
+ "Actor subclass to represent the killer.")
+
+(defclass wink-murder-innocent (wink-murder-actor)
+ ((death-countdown
+ :initform (1+ (random 10))
+ :documentation "The number of ticks to go from dying to dead")))
+
+(defun wink-murder-initialize-actors (players)
+ "Returns a list of `players' wink-murder-actors, where one is the killer."
+ (cl-assert (>= players 4) () "Cannot play with fewer than 4 players")
+ (let* ((killer (1+ (random players)))
+ (actors (cl-loop for i from 1 to players
+ collect (if (eql i killer) (wink-murder-killer :id i) (wink-murder-innocent :id i)))))
+ (mapc (lambda (a)
+ (setf (wink-murder-actor-target a) (wink-murder-random-other a actors)))
+ actors)))
+
+
+
+(cl-defmethod wink-murder-observe ((actor wink-murder-actor))
+ "Base behavior for an actor. Note the ids of the observed target and who
+they are perceived to be targeting."
+ (with-slots (notes (my-target target)) actor
+ (when my-target
+ (with-slots (id (their-target target)) my-target
+ (when their-target
+ (setf notes (cons `(,id . ,(wink-murder-actor-id their-target)) notes)))))))
+
+(cl-defmethod wink-murder-observe ((actor wink-murder-innocent))
+ (when (> 5 (random 11))
+ (with-slots (id target) actor
+ (let* ((new-target (wink-murder-random-other actor (slot-value wink-murder-active-game 'actors)))
+ (new-id (wink-murder-actor-id new-target))
+ (new-status (slot-value new-target 'status)))
+ (wink-murder-add-event
+ (wink-murder-retarget-event :actor-id id :old (wink-murder-actor-id target) :new new-id
+ :message (format "Innocent %d observes %d and sees they are %s" id
+ new-id new-status)))
+ (setf target new-target))))
+ (cl-call-next-method))
+
+(defun wink-murder-eye-contact? (a b)
+ "Given two `wink-murder-actor's, returns t if they are eachother's current target."
+ (and (equal (slot-value a 'target) b)
+ (equal (slot-value b 'target) a)))
+
+(defun neighbors (e lst)
+ (let* ((idx (cl-position e lst))
+ (len (length lst))
+ (left (elt lst (mod (1- idx) len)))
+ (right (elt lst (mod (1+ idx) len))))
+
+ (list left right)))
+
+ (cl-defmethod wink-murder-being-watched? ((killer wink-murder-killer))
+ "Specilized on the killer, returns true when there is a most recent memory,
+and the target is the killer themselves."
+
+ ;; (with-slots (id notes) killer
+ ;; (let* ((most-recent-memory (car notes))
+ ;; (their-target (cdr most-recent-memory)))
+ ;; (and their-target (= id their-target))))
+
+ (> 5 (random 11))
+ )
+
+(cl-defmethod wink-murder-observe ((killer wink-murder-killer))
+ "Specialized behavior for the `wink-murder-killer'."
+ (with-slots (id target) killer
+ (with-slots ((old-id id)) target
+ (if (wink-murder-being-watched? killer)
+ (let* ((new-target (wink-murder-random-other killer (wink-murder-living-innocents wink-murder-active-game)))
+ (new-id (wink-murder-actor-id new-target)))
+ (wink-murder-add-event
+ (wink-murder-retarget-event :actor-id id :old old-id :new new-id
+ :message (format "the killer targets %d" new-id)))
+ (setf target new-target))
+ (when (wink-murder-eye-contact? killer target)
+ (progn
+ (wink-murder-add-event
+ (wink-murder-event :actor-id id :message (format "the killer winks at %d." old-id)))
+ (wink-murder-innocent-die target)))
+ (cl-call-next-method killer)))))
+
+(defun wink-murder-alive-p (actor)
+ "Returns `t' if the actor is alive, otherwise `nil'"
+ (eql (slot-value actor 'status) 'alive))
+
+(defun wink-murder-innocent-die (actor)
+ (with-slots (id status) actor
+ (wink-murder-add-event (wink-murder-event :actor-id id :message "AIIEEEE!!"))
+ (setf status 'dead)))
+
+(defun wink-murder-play (players)
+ "Entry point to start a game of Wink-Murder."
+ (interactive "nnumber of players: ")
+ (with-current-buffer "*WINK-MURDER-LOG*" (erase-buffer))
+ (setq wink-murder-active-game (wink-murder :actors (wink-murder-initialize-actors players)))
+ (while (> (length (wink-murder-living-innocents wink-murder-active-game)) 1)
+ (wink-murder-update wink-murder-active-game))
+ (mapc #'wink-murder-log-event (reverse (slot-value wink-murder-active-game 'events)))
+ (switch-to-buffer "*WINK-MURDER-LOG*"))