"Follow along by entering the following examples in the Lissp REPL.
It will show you the compiled Python and evaluate it. Try variations
that occur to you. To fully understand the examples, you must see
their Python compilation and output. Make sure you install the Hissp
version matching this document.
This document is written like a .lissp file, thoroughly demonstrating
Lissp's (and thereby Hissp's) features from the bottom up with
minimal exposition. This element enclosed in double quotes is a
*Unicode token* serving as the docstring for the module.
Lissp is a lightweight text language representing the Hissp
intermediate language. The Lissp reader parses the Lissp language's
symbolic expressions as Python objects. The Hissp compiler
then translates and assembles these syntax trees into Python code.
Some familiarity with Python is assumed for this tour. Familiarity with
another Lisp dialect is not assumed, but helpful. If you get confused or
stuck, look for the Hissp community chat or try the more expository
Hissp Primer.
You are expected to read through the sections in order. New concepts
will be presented incrementally. Examples of a new concept will
otherwise be limited to what has been demonstrated so far, which may
not be their most natural expression.
"
;;;; Installation
;;; These docs are for the latest development version of Hissp.
;;; Install the latest Hissp version with
;;; $ pip install git+https://github.com/gilch/hissp
;;; Uninstall any old versions first,
;;; or start in a fresh virtual environment.
;;; Start the REPL with
;;; $ lissp
;;; You can quit with EOF or (exit).
;;; Most examples are tested automatically, but details may be dated.
;;; Report issues or try the current release version instead.
;;;; Fragment Tokens
;;; To understand Lissp, let's start with some lexical analysis,
;;; so you can recognize the pieces you're looking at.
;; This is a FRAGMENT TOKEN.
;; You can put Python code inside and the compiler passes it through:
|print('Hello, World!')| ;note surrounding ||
;;; That's all you need! Now you can write anything in Lissp.
;;; In Python. In a fragment token. Just that easy.
;;; Yeah, we're not done.
;; Escape a | by doubling it:
|bin(0b101_101 || 0b111_000)| ;bitwise OR operator
;;; There are a few special cases that don't simply pass through.
;; A MODULE HANDLE abbreviates an import expression:
|collections.abc.| ;note the .|
;; A FULLY-QUALIFIED IDENTIFIER can be thought of as getting
;; attributes from a module handle:
|math..tau.__class__| ;note the ..
;; This is a CONTROL WORD. It compiles to a string literal:
|:word| ;note the |:
;;; Control words control interpretation of other things in some contexts.
;;;; Tuples
;;; To a first approximation, the Hissp intermediate language is made
;;; of Python data representing syntax trees. The nodes are tuples
;;; and the leaves are called ATOMS. Collectively, FORMS, are
;;; evaluable objects.
;;; Pair a `(` (open token) with a `)` (close token) to make a tuple.
;;; The compiler assembles fragments according to simple rules.
;;; Tuples normally compile to function calls.
(|frozenset|) ;call a builtin
(|print| |1| |2| |3|) ;call with arguments
(|print| (|set|) (|list|) (|dict|)) ;nested calls
(|print| |*'abc'| |sep='-'|) ;Python unpacking and keyword arg
(|'wow'.upper|) ;method call
;; Method calls have a special case so you can separate them.
(|.upper| |'amazing'|) ;note the |.
;; What happens if you call an "empty name" in Python?
(|| |1| |*'abc'| |3|) ;That's right, it makes a tuple!
(|dict| (|| (|| |1| |2|) (|| |3| |4|))) ;Make other collections with them.
(|| |1|) ;Be careful with single arguments.
(|| |1| ||) ;Forgot the comma before. Get it?
;;;; Lambda Special Forms
;; This looks like a function call, but it's a special case.
(|lambda| (|*xs|) |[*xs]|) ;list-making lambda expression
(_ |1| |2| |3|) ; _ is previous result that wasn't None in Python shell.
(|lambda| (|i|) (|functools..reduce| |operator..mul| (|range| |i| |0| |-1|) |1|))
(|.update| (|globals|) |factorial=_|) ; _ doesn't work in modules though
(|factorial| |3|)
(|factorial| |4|)
;;;; Quote Special Forms
;;; Looks like a function call, but it's a special case.
;;; Quote forms suppress evaluation and just return the argument form.
(|quote| |math..tau|)
|math..tau|
(|quote| (|print| |42|))
(|print| |42|)
;;;; Object Tokens
;;; Fragment tokens read as str atoms, but they're not the only kind
;;; of OBJECT TOKEN. In many cases, you can drop the ||.
|"I'm a string."| ;use | for a FRAGMENT TOKEN
"I'm a string." ;use " for a UNICODE TOKEN
(|quote| |"I'm a string."|) ;makes sense
(|quote| "I'm a string") ;What did you expect?
|:control word|
:control\ word ;use : for a CONTROL TOKEN (note \ )
(|quote| :control\ word) ;same result
;;; BARE TOKENS don't have a special delimiting character.
|0x_F00|
0xF00 ;LITERAL TOKEN (note compilation)
(|quote| (|None| |False| |...| |42| |4e2| |4+2j|)) ; all str atoms
(|quote| (None False ... 42 4e2 4+2j)) ;six literal tokens (compilation!)
|object|
object ;SYMBOL TOKEN (identifier)
(quote object) ;both symbol tokens (str atoms)
|math.|
math. ;symbol token (module handle)
math..tau ;symbol token (fully-qualified)
(quote math..tau) ;it's still a str atom
;;;; Tagging Tokens
;; Invoke any fully-qualified callable on the next parsed object at READ TIME.
builtins..hex#3840 ;fully-qualified name# is a TAG
builtins..ord#Q ;tags make notation extensible
math..exp#1 ;e^1. Or to whatever. At read time.
builtins..dict#((1 2) (3 4)) ;no quote or || (note compilation!)
;;; Except for str atoms, atoms in Hissp should evaluate to themselves.
;;; But when the atom lacks a Python literal notation, the compiler is
;;; in a pickle!
builtins..float#inf ;had to fall back to a pickle
fractions..Fraction## 2 3 ;more #s for more args (note ##)
;;; Fully-qualified tags are not the only type of tagging token.
builtins..complex# imag=2 ;keyword argument via KWARG TOKEN
builtins..bytes##encoding=ascii|bytes| ; kwarg can be first (pass-by-name)
;; Yes, Kwargs are a type of object special-cased in the reader. They're
;; only meant for use at read time, but they're allowed to survive to
;; run time for debugging purposes.
spam=eggs
;; use ; for a COMMENT TOKEN (like this one)
;; We've seen these a lot. They are, in fact, a type of object token!
;; The reader normally discards them, but here it's a tag argument.
;; Tagging tokens compose like functions.
builtins..repr# builtins..repr# ; I'm a Comment and
;; I'm another line in the same block!
;;;; Special Tags
;; HARD QUOTE (') is a SPECIAL TAG which abbreviates the quote special form
(quote ''1)
''x
'\'x'
builtins..complex# *=(4 2) ; unpack via STARARG TOKEN (special tag Kwarg)
_#"The DISCARD TAG (_#) is a special tag that omits the next form.
It's a way to comment out code structurally.
It can also make Unicode token comments like this one.
(But the need to escape double quotes might make ;; comments easier.)
This would show up when compiled if not for _#.
Of course, a string statement like this one wouldn't do anything
in Python, even if it were compiled in.
"
(print 1 _#(I'm not here!) 2 3)
;;; The INJECT special tag compiles and evaluates the next form at
;;; read time and injects the resulting object directly into the Hissp
;;; tree, like a fully-qualified tag does.
'(1 2 (operator..add 1 2)) ;Quoting happens at compile time.
'(1 2 .#(operator..add 1 2)) ;Inject happens at read time.
(fractions..Fraction 1 2) ;Run-time call. Equivalent compiled code.
.#(fractions..Fraction 1 2) ;Read-time call. Equivalent read object.
;; An injected Unicode token acts like a fragment token, but can have
;; things like newlines and string escape codes.
(lambda (a b c)
.#"(-b + (b**2 - 4*a*c)**0.5)
/(2*a)") ;quadratic formula
;;;; Symbol Token Munging
'+ ;read-time munging of invalid identifiers
'Also-a-symbol! ;Alias for 'AlsoQzH_aQzH_symbolQzBANG_
'π ;Alias for 'A (Unicode normal form KC)
'-<>>
:-<>> ;doesn't represent identifier (no munge)
: ;shortest control word
;;;; Escaping with \
'SPAM\ \"\(\)\;EGGS ;would terminate symbol if not escaped
'\42 ;digits can't start identifiers
'\.
'\\
'\a\b\c ;escapes allowed here (not required)
1\2 ;backslashes work in other tokens
N\one
;;;; Advanced Call Arguments
(dict |spam="foo"| |eggs="bar"| |ham="baz"|) ; kwargs via fragment tokens
(dict : spam "foo" eggs "bar" ham "baz") ; no || here (note the :)
(print 1 2 3 |sep="-"|)
(print : :? 1 :? 2 :? 3 sep "-") ;:? is a positional target.
(print 1 2 3 : sep "-") ;Args before : implicitly pair with :?.
;; Python unpacking, positional, and keyword arguments.
(print 1 |*"abc"| 2 |*"xyz"| |**{"sep": "-"}| |flush=True| |**{"end": "!?\n"}|)
;; You can do the same things without || using control words.
(print 1 ;Implicitly a positional :? target.
: :* "abc" ;Target :* to unpack iterable.
:? 2 ;:? is still allowed after :*.
:* "xyz" ;:* is a repeatable positional target.
:** |{"sep": "-"}| ;Target :** to unpack mapping.
flush True ;Kwargs still allowed after :**.
:** |{"end": "!?\n"}|) ;Multiple :** allowed too.
(print : :? "Hello, World!")
(print "Hello, World!" :) ;Same. Slid : over. Compare.
(print "Hello, World!") ;No : is the same as putting it last!
;;;; Advanced Lambda Parameters
;; Python parameter types are rather involved.
(lambda (a b |/| c d |e=1| |f=2| |*args| |h=4| i |j=1| |**kwargs|)
(print (locals)))
;; Lambda control words can do all of them.
;; Like calls, they are all pairs. :? means no default.
(lambda (: a :? b :? :/ :? ;positional only
c :? d :? ;normal
e 1 f 2 ;default
:* args h 4 i :? j 1 ;star args, keyword
:** kwargs)
;; Body.
(print (globals))
(print (locals)) ;side effects
b) ;last value is returned
(lambda (|*xs|)) ;star arg
(lambda (|*| |kw|)) ;keyword only (note comma)
(lambda (: :* xs)) ;Star arg must pair with star, as Python.
(lambda (: :* :? kw :?)) ;Empty star arg, so kw is keyword only.
(lambda (:* : kw :?)) ;Slid : right one pair. Still a kwonly.
(lambda (:* kw :)) ;Implicit :? is the same. Compare.
(lambda (:* kw)) ;Kwonly! Not star arg! Final : implied.
(lambda (a b : x None y None)) ;Normal, then positional defaults.
(lambda (:* a b : x None y None)) ;Keyword only, then keyword defaults.
(lambda (spam eggs) eggs) ;Simple cases look like other Lisps, but
((lambda abc ; params need not actually be a tuple.
(print c b a)) ;There are three parameters.
3 2 1)
(lambda (:)) ;Explicit : still allowed with nothing.
(lambda : (print "oops")) ;Thunk resembles Python.
((lambda :x1 x)) ;Control words are strings are iterable.
;;;; Operators
;;; Hissp is simpler than Python. No operators! Use calls instead.
(operator..add 40 2)
;; We'll be reusing this one in later sections.
(.update (globals) : + operator..add) ;assignment (identifier munged)
(+ 40 2) ;no operators (Still a function call!)
|40+2| ;always worked, of course (just Python)
;;;; Control Flow
;;; Hissp is simpler than Python. No control flow! Use higher-order functions instead.
(any (map print "abc")) ; Loops!
((.get (dict : y (lambda : (print "Yes!"))
n (lambda : (print "Canceled.")))
(input "enter y/n> ")
(lambda : (print "Unrecognized input.")))) ; Branches!
;;; Don't worry, Hissp metaprogramming will make this much easier
;;; (and Hissp comes bundled with macros for these things), but our
;;; limited tools so far are enough for a ternary operator.
;; boolean, consequent, alternate
(.update (globals) : if_else (lambda bca ((.__getitem__ (|| c a) (not b)))))
(any (map (lambda x (if_else |x%2|
(lambda : (print x 'odd))
(lambda : (print x 'even))))
(range 4))) ; Both!
;;;; Templates
;; SOFT QUOTE special tag (`) starts a template
`print ;Automatic full qualification!
`foo+2 ;Not builtin. Still munges.
`(print "Hi") ;Code as data. Seems to act like quote.
'`(print "Hi") ;But it's calling the "empty name".
;; UNQUOTE special tag (,) interpolates. Only valid in a template.
`(print ,(.upper "Hi"))
`(,'foo+2 foo+2) ;Interpolations not auto-qualified!
;; SPLICE special tag (,@) interpolates and unpacks. Only valid in a tuple in a template.
`(print ,@"abc")
`(print (.upper "abc")) ;Template quoting is recursive
`(print ,@(.upper "abc")) ; unless suppressed by an unquote.
;;; Full qualification prevents accidental name collisions in
;;; programmatically generated code. But full qualification doesn't work
;;; on local variables, which can't be imported. For these, we use a
;;; GENSYM special tag ($#) which (instead of a qualifier) adds a prefix
;;; to ensure a variable can only be used in the same template it was
;;; defined in. It contains a hash of three things: the code being read,
;;; __name__, and a count of the templates the reader has seen so far.
`($#eggs $#spam $#bacon $#spam)
;; Each new template increases the count, so it results in a new hash,
`$#spam
;; even if the code is identical.
`$#spam
;;; However, the hashing procedure is fully deterministic, so builds are
;;; reproducible even when they contain generated symbols.
;; If you don't specify, by default, the gensym hash is a prefix,
;; but you can put them anywhere in the symbol. $ marks the positions.
;; Lacking a gensym prefix, it gets fully qualified by the template.
`$#spam$.$eggs$
;; This is typically used for partially-qualified variables,
;; i.e., with an explicit namespace that is not a module handle.
;; The interpolation suppressed auto-qualification.
`,'$#self.$foo
;;; You can use templates to make collections with interpolated values.
;;; When your intent is to create data rather than code, unquote
;;; each element.
;; (Uses `+` from ;;;; Operators)
(list `(,@"abc"
,1
,(+ 1 1)
,(+ 1 2)))
`(0 "a" 'b) ;Beware of Unicode tokens and symbols.
`(,0 ,"a" ,'b) ;Just unquote everything in data templates.
(dict `((,0 ,1)
,@(.items (dict : spam "eggs" foo 2)) ; dict unpacking
(,3 ,4)))
;;;; Macros
;;; We can use functions to to create forms for evaluation.
;;; This is metaprogramming: code that writes code.
(.update (globals) ;assign fills template to make a form
: assign
(lambda (key value)
`(.update (globals) : ,key ,value)))
;; Notice the arguments to it are quoted.
(assign 'SPAM '"eggs") ;resulting in a valid Hissp form
(hissp.compiler..readerless _) ;Hissp can compile it,
(eval _) ; and Python can evaluate that.
SPAM ;'eggs'
;;; We can accomplish this more easily with a MACRO FORM.
;;; Unqualified invocations are macro forms if the identifier is in
;;; the current module's _macro_ namespace. The REPL includes one, but
;;; .lissp files don't have one until you create it.
(dir) ;note _macro_
(dir _macro_)
;;; Macros run at compile time, so they get all of their arguments
;;; unevaluated. The compiler inserts the resulting Hissp
;;; (the EXPANSION) at that point in the program.
(setattr _macro_ 'assign assign) ;we can use assign as a MACRO FUNCTION
;; Like special forms, macro forms look like ordinary function calls.
(assign SPAM "ham") ;This runs a metaprogram!
SPAM ;'ham'
;;; We almost could have accomplished this one with a function, but we'd
;;; have to either quote the variable name or use a : to pass it in as a
;;; keyword. The macro form is a little shorter. Furthermore, the
;;; globals function gets the globals dict for the current module. Thus,
;;; an assign function would assign globals to the module it is defined
;;; in, not the one where it is used! You could get around this by
;;; walking up a stack frame with inspect, but that's brittle. The macro
;;; version just works because it writes the code in line for you, so
;;; the globals call appears in the right module.
;;; Macros are a feature of the Hissp compiler. Macro expansion happens
;;; at compile time, after the reader, so macros also work in readerless
;;; mode, or with Hissp readers other than Lissp, like Hebigo.
;;; UNQUALIFIED TAGS work if there's a corresponding name ending in #
;;; (i.e. QzHASH_) in _macro_. Metaprograms for tagging tokens run at
;;; read time, but (like ') may simply return code that runs later.
(setattr _macro_ 'chr\# chr) ;note \# (would be a tag token otherwise)
'chr#42 ;note hard quote
;; Hissp already comes with a define macro for attribute assignment.
(help hissp.._macro_.define)
;; An invocation fully qualified with _macro_ is a macro form.
(hissp.._macro_.define SPAM "eggs") ;Note SPAM is not quoted.
SPAM ;'eggs'
;; The REPL's default _macro_ namespace already has the bundled macros.
(help _macro_.define)
;;;; Macro Technique
;;; (Examples here use `+` from ;;;; Operators)
;; Use a template to make Hissp.
(define _macro_.triple (lambda x `(+ ,x (+ ,x ,x))))
(triple 4) ;12
(define loud-number (lambda x (print x) x))
(triple (loud-number 14)) ;Triples the *code*, not just the *value*.
;; But what if we want the expanded code to only run it once?
;; We can use a lambda to make a local variable and immediately call it.
((lambda x (+ x (+ x x)))
(loud-number 14))
;; Python also allows us to use a default argument up front.
((lambda (: x (loud-number 14))
(+ x (+ x x))))
;; Let's try making a template to produce code like that.
(define _macro_.oops-triple
(lambda (expression)
`((lambda (: x ,expression) ; Expand to lambda call for a local.
(+ x (+ x x))))))
(oops-triple 14) ;Oops. Templates qualify symbols!
;; Remember, a gensym hash prefix is an alternative to qualification
;; for locals. (Thus, templates don't qualify them.)
(define _macro_.once-triple
(lambda x
`((lambda (: $#x ,x)
(+ $#x (+ $#x $#x))))))
(once-triple (loud-number 14))
;;; Notice the special QzMaybe_ qualifier generated by this template.
;;; Templates create these for symbols in the invocation position (first
;;; tuple element) when they can't tell if _macro_ would work. The
;;; compiler replaces a QzMaybe_ with _macro_ if it can resolve the
;;; resulting symbol, and omits it otherwise.
`(+ 1 2 3 4)
;; Outside-in recursive macro. (A multiary +). Note the QzMaybe_.
;; If this had been qualified like a global instead, the recursion
;; wouldn't work.
(define _macro_.+
(lambda (: first 0 :* args) ; 0 with no args. Try it!
(.__getitem__ ; Tuple method. Templates produce tuples.
`(,first ; Result when no args left.
(operator..add ,first (+ ,@args))) ; Otherwise recur.
(bool args)))) ; Bools are ints, remember?
(+ 1 2 3 4)
;; Notice that a new template doesn't qualify + with QzMaybe_ now that
;; it detects a macro with that name.
`(+ 1 2 3 4)
;; Recursive macros can also expand from the inside outwards, although
;; it's less natural in this case.
(define _macro_.*
(lambda (: first 1 second 1 :* args)
(.__getitem__
`((operator..mul ,first ,second)
(* (operator..mul ,first ,second) ,@args))
(bool args))))
;; Notice that the stacked expansion comments left by the compiler
;; have been squashed together. You can count the #s to see how many.
;; 4 of them were recursive invocations and had to use the QzMaybe.
;; The 5th didn't, and that accounts for all 5 calls in the expansion.
(* 1 2 3 4 5 6)
;;; Hissp comes with some helper functions meant only for use
;;; interactively or in metaprograms. The compiled output isn't
;;; dependent on Hissp (STANDALONE PROPERTY) when used correctly.
;; Three of the helpers expand macros.
(hissp..macroexpand1 '(print 1 2 3)) ;not a macro form (no change)
(hissp..macroexpand1 '(* 1 2 3)) ;expanded (but still a macro form)
(hissp..macroexpand '(* 1 2 3)) ;repeats while it's a macro form
(hissp..macroexpand '(+ 1 2 3)) ;but doesn't check subforms
(hissp..macroexpand_all '(+ 1 2 3)) ;expands all macro subforms
;; Some of the helpers are predicates for inspecting code.
(pprint..pp
(list
(itertools..starmap
(lambda xy (|| x y.__name__))
(filter (lambda x (|x[1]| |x[0]|))
(itertools..product '(:control re. "string" 'quoted () 1 '2)
(|| hissp..is_control
hissp..is_import
hissp..is_node
hissp..is_str
hissp..is_symbol
hissp..is_hissp_string
hissp..is_lissp_unicode
hissp..is_string_literal))))))
;; Macros only work as invocations, not arguments!
(functools..reduce * '(1 2 3 4)) ;Oops.
(functools..reduce (lambda xy (* x y)) ;Invocation, not argument.
'(1 2 3 4))
;;; Sometimes you actually do want a name collision (or "capture"),
;;; when the macro user should expect an implicit new local binding
;;; (an ANAPHOR). Don't qualify and don't gensym in that case.
;;; Unquoting suppresses the recursive template quoting of tuples,
;;; while the hard quote doesn't qualify symbols, so this combination
;;; suppresses auto-qualification.
(define _macro_.XY
(lambda (: :* body)
`(lambda (,'X ,'Y) ;,'X instead of $#X
,body)))
(functools..reduce (XY * X Y) ;Invocation, not argument!
'(1 2 3 4))
((XY + Y X) "Eggs" "Spam")
;; It's possible for a macro to shadow a global. They live in different namespaces.
(+ 1 2 3 4) ;_macro_.+, not the global.
(functools..reduce + '(1 2 3 4)) ;Global function, not the macro!
(dir) ;Has QzPLUS_, but not QzSTAR_.
(dir _macro_) ;Has both.
;; Notice the qualifier on sep. Qualifying a keyword doesn't make sense.
(define _macro_.p123
(lambda (sep)
`(print 1 2 3 : sep ,sep)))
;; Note the : didn't have to be quoted here, because it's in a macro
;; invocation, not a call. The compiler also ignored the qualifier
;; on sep, because it's a kwarg.
(p123 :)
;;;; Compiling and Running Files
;;; The ``lissp`` shell command can run a .lissp file as __main__.
;;; Python cannot import .lissp directly. Compile it to .py first.
;;; Hissp could theoretically import .lissp via import hooks,
;;; but that would break the compiled Hissp standalone property,
;;; by adding a dependency on the ``hissp`` package for imports.
;; Finds spam.lissp & eggs.lissp in the current package & compile to spam.py & eggs.py
(.write_text (pathlib..Path "eggs.lissp")
"(print \"Hello World!\")")
(.write_text (pathlib..Path "spam.lissp")
'hissp.reader..Comment.contents#
;; (print "Hello from spam!")
;; (.update (globals) : x 42)
_#"<- A string from a comment. Doesn't need \" escape.")
(hissp.reader..transpile __package__ 'spam 'eggs) ;Side effects on compilation.
spam..x ;Compiled modules are cached.
eggs.
(importlib..reload spam.) ;Side effects again on .py reload.
(any (map (lambda f (os..remove f)) ;Cleanup.
'(eggs.lissp spam.lissp spam.py eggs.py)))
;;;; The Bundled Macros and Tags
;;; As a convenience, the REPL comes with the bundled macros
;;; already defined at start up. They're in the _macro_ namespace.
(dir _macro_)
;;; This is a copy of of the following namespace.
hissp.macros.._macro_
(dir hissp.macros.._macro_)
;;; Notice its containing module. Take a minute to read its docstring.
(help hissp.macros.)
;;; As a convenience, hissp.__init__ imports it as well:
hissp.._macro_
;;; The macros will still be available from there even if you clobber
;;; your _macro_ copy. Recall that you can invoke macros using their
;;; fully-qualified names.
;;; The bundled macros have individual docstrings with usage examples.
;;; At this point in the tour, you should be able to understand them.
(help _macro_.define)
;;; Two particularly important ones to know are alias and the prelude.
;;; Unlike the REPL, Lissp modules do not have a _macro_ namespace by
;;; default. A typical Lissp module will start with a fully-qualified
;;; invocation of something like one of these to create the _macro_
;;; namespace for the module.
;;; Aliases can give you access to macros defined elsewhere using
;;; short qualifying tags, as well as attributes of ordinary modules.
(help _macro_.alias)
;;; The prelude copies _macro_ from hissp._macro_ like the REPL, defines
;;; some Python interop helper functions, and imports Python's standard-library
;;; functional programming utilities from operator and itertools.
(help _macro_.prelude)
;;; The docstrings use reStructuredText markup. While readable as plain
;;; text in the help console, they're also rendered as HTML using Sphinx
;;; in Hissp's online API docs. Find them at https://hissp.rtfd.io
;;; Familiarize yourself with a macro suite, such as the bundled macros.
;;; It makes Hissp that much more usable.