Lissp Whirlwind Tour#

(Outputs hidden for brevity.)
"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 these syntax trees to Python expressions.

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
docstring for the module.

To fully understand these examples, you must see their Python
compilation and output. Some familiarity with Python is assumed.
Install the Hissp version matching this document. Follow along by
entering these examples in the REPL. It will show you the compiled
Python and evaluate it. Try variations that occur to you.

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
Hissp Primer.
"

;;;; 1 Installation

;;; Install Hissp from PyPI with
;;; $ pip install hissp==0.4
;;; Uninstall any old versions first,
;;; or start in a fresh virtual environment.
;;; Start the REPL with
;;; $ lissp
;;; You can quit with EOF or (exit).

;;;; 2 Simple Atoms

;;; To a first approximation, the Hissp intermediate language is made
;;; of Python tuples representing syntax trees. The nodes are tuples
;;; and the leaves are called "atoms". Simple atoms in Lissp are
;;; written the same way as Python.

;;;; 2.1 Singleton

None
...                                 ;Ellipsis

;;;; 2.2 Boolean

False                               ;False == 0
True                                ;True == 1

;;;; 2.3 Integer

42
-10_000
0x10
0o10
0b10
0b1111_0000_0000
0xF00

;;;; 2.4 Floating-Point

3.
-4.2
4e2
-1.6e-2

;;;; 2.5 Complex

5j                                  ;imaginary
4+2j                                ;complex
-1_2.3_4e-5_6-7_8.9_8e-7_6j         ;Very complex!

;;;; 3 Simple Tuples

;; Tuples group any atoms with (). Data tuples start with '.
'(None 2 3)
'(True
  False)

;;;; 4 Symbolic Atoms

;;;; 4.1 Identifiers

object                              ;Python identifiers work in Lissp.
object.__class__                    ;Attribute identifier with dot, as Python.
object.__class__.__name__           ;Attributes chain.

;;;; 4.2 Imports

math.                               ;Module handles import!
math..tau                           ;Fully-qualified identifier. (Module attribute.)
collections.abc.                    ;Submodule handle. Has package name.

builtins..object.__class__          ;Qualified attribute identifier.
collections.abc..Sequence.__class__.__name__ ;Chaining.

;;;; 5 Simple Forms and Calls

;;; "Forms" are any data structures that can be evaluated as a Hissp program.
;;; Simple atoms are forms. They simply evaluate to an equivalent object.

0x2a

;;; Tuples can also be forms, but their evaluation rules are more complex.
;;; The common case is a function call. For that, the first element must
;;; be a callable. The remainder are arguments.

(print 1 2 3)                       ;This one compiles to a function call.
'(print 1 2 3)                      ;This one is a data tuple.

;;; Data tuples and calls are enough to make simple collections.

'(1 2 3)                            ;tuple
(list '(1 2 3))
(set '(1 2 3))
(dict '((1 2) (3 4)))               ;Uses nested tuples.
(bytes '(98 121 116 101 115))

(help sum)                          ;Python's online help function still works.

;;;; 6 String Atoms

:control-word                       ;Colon prefix. Similar to Lisp ":keywords".
'symbol                             ;Apostrophe prefix. Represents identifier.

;;;; 6.1 Munging

'+                                  ;Read-time munging of invalid identifiers.
'Also-a-symbol!                     ;Alias for 'AlsoQz_aQz_symbolQzBANG_
'𝐀                                  ;Alias for 'A (unicode normal form KC)
'-<>>
:-<>>                               ;Don't represent identifiers, don't munge.
:                                   ;Still a control word.

;;;; 6.2 Escaping

'SPAM\ \"\(\)\;EGGS                 ;These would terminate a symbol if not escaped.
'\42                                ;Digits can't start identifiers.
'\.
'\\
'\a\b\c                             ;Escapes allowed, but not required here.
1\2                                 ;Backslashes work in other atoms.
N\one

;;;; 6.3 String Literals

"raw string"
'not-string'                        ;symbol
#"Say \"Cheese!\" \u263a"           ;Hash strings process Python escapes.
"Say \"Cheese!\" \u263a"            ;Raw strings don't.

"string
with
newlines
"                                   ;Same as #"string\nwith\nnewlines\n".

"one\"
string\\"                           ;Tokenizer expects paired \'s, even raw.

;;;; 7 Advanced Calls

(dict :)                            ;Left paren before function! Notice the :.

;; All arguments pair with a target! No commas!
(dict : spam "foo"  eggs "bar"  ham "baz")

(print : :? 1  :? 2  :? 3  sep "-") ;:? is a positional target.
(print 1 : :? 2  :? 3  sep "-")     ;Arguments before : implicitly pair with :?.
(print 1 2 : :? 3  sep "-")         ;Keep sliding : over. It's shorter.
(print 1 2 3 : sep "-")             ;Next isn't a :?. The : stops here.

(print 1                            ;Implicitly a positional :? target.
       : :* "abc"                   ;Target :* to unpack iterable.
       :? 2                         ;:? is still allowed after :*.
       :* "xyz"                     ;:* is a repeatable positional target.
       :** (dict : sep "-")         ;Target :** to unpack mapping.
       flush True                   ;Kwargs still allowed after :**.
       :** (dict : 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!

(.upper "shout!")                   ;Method calls need a . and a "self".
(.float builtins. 'inf)             ;Method call syntax, though not a method.
(builtins..float 'inf)              ;Same effect, but not method syntax.

;;;; 7.1 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. This is still a function call!

;;;; 8 Simple Lambdas

;;; Lambdas are one of Hissp's two "special forms".
;;; They look like calls, but are special-cased in the Hissp compiler
;;; to work differently. The first element must be 'lambda', the second
;;; is the parameters, and finally the body.

(.update (globals)
         : greet
         (lambda (salutation name)
           (print (.format "{}, {}!"
                           (.title salutation)
                           name))))
(greet "hello" "World")
(greet "hi" "Bob")

;;;; 8.1 Obligatory Factorial I

;;; We now have just enough to make more interesting programs.

(.update (globals)
         : factorial_I
         (lambda (i)
           (functools..reduce operator..mul
                              (range i 0 -1)
                              1)))
(factorial_I 0)
(factorial_I 3)
(factorial_I 5)

;;;; 8.2 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!")) ;Branches!
             n (lambda () (print "Canceled.")))
       (input "enter y/n> ")
       (lambda () (print "Unrecognized input."))))

;;; Don't worry, Hissp metaprogramming will make this much easier,
;;; but our limited tools so far are enough for a ternary operator.

(.update (globals) : bool->caller (dict))

;; True calls left.
(operator..setitem bool->caller True (lambda (L R) (L)))

;; False calls right.
(operator..setitem bool->caller False (lambda (L R) (R)))

(.update (globals)
         : ternary
         (lambda (condition then_thunk else_thunk)
           ((operator..getitem bool->caller (bool condition))
            then_thunk else_thunk)))

;;;; 8.3 Obligatory Factorial II

;; Now we have enough for a recursive version.
(.update (globals)
         : factorial_II
         (lambda (i)
           (ternary (operator..le i 1)
                    (lambda () 1)
                    (lambda ()
                      (operator..mul i (factorial_II (operator..sub i 1)))))))
(factorial_II 5)

;;;; 9 Advanced Lambdas

;; Python parameter types are rather involved. Lambda does 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, key word
         :** kwargs)
  ;; Body. (Lambdas return empty tuple when body is empty.)
  (print (globals))
  (print (locals))                  ;side effects
  b)                                ;last value is returned

(lambda (: a :?  b :?  c 1))        ;Note the : separator like calls.
(lambda (a : b :?  c 1))            ;`a` now implicitly paired with :?.
(lambda (a b : c 1))                ;Next isn't paired with :?. The : stops here.

(lambda (: :* a))                   ;Star arg must pair with star, as Python.
(lambda (: :* :?  x :?))            ;Empty star arg, so x is keyword only.
(lambda (:* : x :?))                ;Slid : over one. Still a kwonly.
(lambda (:* x :))                   ;Implicit :? is the same. Compare.
(lambda (:* a))                     ;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 not strictly required to be a tuple.
   (print c b a))                   ;There are three parameters.
 3 2 1)

(lambda (:))                        ;Explicit : still allowed with no params.
(lambda : (print "oops"))           ;Thunk resembles Python.
((lambda :x1 x))                    ;Control words are strings are iterable.

;;;; 10 Quote

;;; Quote is the only other special form. Looks like a call, but isn't.

;;; A "form" is any Hissp data that can be evaluated.
;;; Not all data is a valid program in Hissp. E.g. ``(7 42)`` is a
;;; tuple, containing the integers 7 in the function position, and 42
;;; after in the first argument position. It would compile to a
;;; syntactically-valid Python program, but evaluation would crash,
;;; because ints are not callable in Python. Try it.

;;; Quotation suppresses evaluation of Hissp data.
;;; Treating the code itself as data is the key concept in metaprogramming.

(quote (7 42))

;;; Other objects evaluate to themselves, but strings and tuples have
;;; special evaluation rules in Hissp. Tuples represent invocations of
;;; functions, macros, and special forms.

(quote (print 1 2 3 : sep "-"))     ;Just a tuple.

;;; Notice how the string gets an extra layer of quotes vs identifiers.
;;; This particular tuple happens to be a valid form.

;; The readerless function runs the Hissp compiler without the Lissp reader.
;; (Remember, _ is the last result that wasn't None in the Python REPL.)
(hissp.compiler..readerless _)      ;It compiles to Python
(eval _)                            ; and Python can evaluate that.

;;; Programmatically modifying the data before compiling it is when
;;; things start to get interesting, but more on that later.

;;; Hissp-level strings contain Python code to include in the compiled
;;; output. These usually contain identifiers, but can be anything.
;;; Thus, Lissp identifiers read as strings at the Hissp level.

(quote identifier)                  ;Just a string.

;;; The raw strings and hash strings in Lissp ("..."/#"..." syntax)
;;; also read as strings at the Hissp level, but they contain a Python
;;; string literal instead of a Python identifier.

(quote "a string")                  ;"..."/#"..." is reader syntax!
(eval (quote "a string"))           ;Python code. For a string.

;;; Quoting does not suppress munging, however. That happens at read
;;; time. Quoting doesn't happen until compile time.

(quote +)

;; Quoting works on any Hissp data.
(quote 42)                          ;Just a number. It was before though.

;;; Strings in Hissp are also used for module handles and control
;;; words. The compiler does some extra processing before emitting these
;;; as Python code. Quoting suppresses this processing too.

math.                               ;Compiler coverts this to an import.
(quote math.)                       ;Quoting suppresses. No __import__.
(quote :?)                          ;Just a string. It was before though?
:?                                  ;Just a string?
((lambda (: a :?) a))               ;Oops, not quite! Contextual meaning here.
((lambda (: a (quote :?)) a))       ;Just a string. Even in context.

;;;; 11 Simple Reader Macros

;;; Reader macros are metaprograms to abbreviate Hissp and don't
;;; represent it directly. Tags apply to the next parsed Hissp object
;;; at read time, before the Hissp compiler sees it, and thus before
;;; they are compiled and evaluated. Tags end in # except for a few
;;; builtins-- ' ! ` , ,@

;;;; 11.1 Quote

;;; The ' reader macro is simply an abbreviation for the quote special form.

'x                                  ;(quote x). Symbols are just quoted identifiers!
'(print "Hi")                       ;Quote to reveal the Hissp syntax tree.

;;;; 11.2 Template Quote

;;; (Like quasiquote, backquote, or syntax-quote from other Lisps.)
;;; This is a DSL for making Hissp trees programmatically.
;;; They're very useful for metaprogramming.

`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 making a program to create the data.
`(print ,(.upper "Hi"))             ;Unquote (,) interpolates.

`(,'foo+2 foo+2)                    ;Interpolations not auto-qualified!
`(print ,@"abc")                    ;Splice unquote (,@) interpolates and unpacks.
`(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) which adds a prefix containing a hash of the code being
;;; read, __name__, and a count of the templates the reader has seen,
;;; instead of a qualifier to ensure a variable can only be used in the
;;; same template it was defined in.

`($#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 deteministic, 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 §7.1.)
(list `(,@"abc"
        ,1
        ,(+ 1 1)
        ,(+ 1 2)))

`(0 "a" 'b)                         ;Beware of strings and symbols.
`(,0 ,"a" ,'b)                      ;Just unquote everything in data templates.

(dict `((,0 ,1)
        ,@(.items (dict : spam "eggs"  foo 2)) ;dict unpacking
        (,3 ,4)))

;;;; 12 Compiler Macros

;;; We can use functions to to create forms for evaluation.
;;; This is metaprogramming: code that writes code.

(.update (globals)                  ;assign fills in a template to make a form.
         : assign
         (lambda (key value)
           `(.update (globals) : ,key ,value)))

;; Notice the arguments to it are quoted.
(assign 'SPAM '"eggs")              ;The result is 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 invocation.

;;; Unqualified invocations are macro invocations 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)
(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. Like special forms,
;;; macro invocations look like function calls, but aren't.

(setattr _macro_ 'assign assign)    ;We can use our assign function as a macro!

;; Macro invocations look like ordinary function calls, but they aren't.
(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 invocation 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. Macroexpansion happens at
;;; compile time, after the reader, so macros also work in readerless
;;; mode, or with Hissp readers other than Lissp, like Hebigo.

;; Hissp already comes with a define macro for global assignment.
;; Our assign macro just re-implemented this.
(help hissp.._macro_.define)

;; An invocation qualified with _macro_ is a macro invocation.
(hissp.._macro_.define SPAM "eggs") ;Note SPAM is not quoted.
SPAM                                ;'eggs'

;; See the macro expansion by calling it like a method with all arguments quoted.
;; This way, the callable isn't qualified with _macro_, so it's a normal call.
(.define hissp.._macro_ 'SPAM '"eggs") ;Method syntax is never macro invocation.

;; The REPL's default _macro_ namespace already has the bundled macros.
(help _macro_.define)

;;;; 12.1 Macro Technique

;;; (Examples here use `+` from §7.1.)

(setattr _macro_
         'triple
         (lambda (x)
           `(+ ,x (+ ,x ,x))))      ;Use a template to make Hissp.
(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.
(setattr _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 qualified them.)
(setattr _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 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.
(setattr _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.
(setattr _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 # to see how many.
;; 4 of them were recursive invocations and had to use the QzMaybe.
;; The 5th didn't, and that accounds for all 5 calls in the expansion.
(* 1 2 3 4 5 6)

;; 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 normal quote doesn't qualify symbols, so this combination
;;; suppresses auto-qualification.

(setattr _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.
(setattr _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 :)

;;;; 13 Compiling and Running Files

;;; ``$ lissp`` can run a .lissp file as __main__.
;;; You cannot import .lissp directly. Compile it to .py first.

;; 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")
             #"(print \"Hello from spam!\")
(.update (globals) : x 42)")
(hissp.reader..transpile __package__ 'spam 'eggs) ; Side effects on compilation

spam..x                             ; and import!
spam..x                             ;Python caches imports.
eggs.

(any (map (lambda f (os..remove f)) ;Cleanup.
     '(eggs.lissp spam.lissp spam.py eggs.py)))

;;;; 14 The Bundled Macros

;;; To make it more usable, 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 module.

hissp.._macro_
(dir hissp.._macro_)

;;; Notice its containing module. Take a minute to read its docstring.

(help hissp.macros.)

;;; 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.

(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
;;; abbreviated qualifiers, 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 utilities.

(help _macro_.prelude)

;;; The dosctrings 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.

;;;; 15 Advanced Reader Macros

;;;; 15.1 The Discard Macro

_#"The discard reader macro _# omits the next form.
It's a way to comment out code structurally.
It can also make block comments like this one.
This would show up when compiled if not for _#.
Of course, a string expression like this one wouldn't do anything
in Python, even if it were compiled in. But the need to escape double
quotes might make ;; comments easier.
"
(print 1 _#(I'm not here!) 2 3)

;;;; 15.2 Fully-Qualified Reader Macros

;; Invoke any fully-qualified callable on the next parsed object at read time.
builtins..hex#3840                  ;Fully-Qualified name ending in # is a reader macro.
builtins..ord#Q                     ;Reader macros make literal notation extensible.
math..exp#1                         ;e^1. Or to whatever number. At read time.

;; Reader macros compose like functions.
'hissp.munger..demunge#Qz_QzLT_QzGT_QzGT_   ;Note the starting '.
''x
'\'x

;; The reader normally discards them, but
'builtins..repr#;comments are parsed objects too!

;;; Except for strings and tuples, objects in Hissp should evaluate
;;; to themselves. But when the object lacks a Python literal notation,
;;; the compiler is in a pickle!

builtins..float#inf

;;;; 15.3 Inject

;;; The 'inject' reader macro compiles and evaluates the next form at
;;; read time and injects the resulting object directly into the Hissp
;;; tree, like a fully-qualified reader macro 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 eval. Compiles to equivalent code.
.#(fractions..Fraction 1 2)         ;Read time eval. Compiles to equivalent object.

;;; Recall that Hissp-level string objects can represent
;;; arbitrary Python code. It's usually used for identifiers,
;;; but can be anything, even complex formulas.

(lambda abc
  ;; Hissp may not have operators, but Python does.
  .#"(-b + (b**2 - 4*a*c)**0.5)/(2*a)")

;;; Remember the raw string and hash string reader syntax makes Python-
;;; level strings, via a Hissp-level string containing a Python string
;;; literal. It is NOT for creating a Hissp-level string, which would
;;; normally contain Python code. Use inject for that.

'"a string"                         ;Python code for a string. In a string.
;; Injection of an object to the Hissp level. In this case, a string object.
'.#"a string"                       ;Quoting renders a Hissp-level string as data.

;; Objects without literals don't pickle until the compiler has to emit
;; them as Python code. That may never happen if another macro gets it.
'builtins..repr#(re..compile#.#"[1-9][0-9]*" builtins..float#inf)
re..compile#.#"[1-9][0-9]*"

;; Statement injections work at the top level only.
.#"from operator import *"          ;All your operator are belong to us.

;;;; 15.4 Extra (!), the Final Builtin Reader Macro

;;; Reader macros have one primary argument, but additional arguments
;;; can be passed in with the extra macro !. A tag consumes the next
;;; parsed object, and if it's an Extra, consumes one again. Thus,
;;; extras must be written between the tag and primary, but because
;;; they're often optional refinements, which are easier to define as
;;; trailing optional parameters in Python functions, they get passed in
;;; after the primary.

(setattr _macro_ 'L\# en#list) ; (help _macro_.en\#)


L#primary
L#!1 primary

;; Alias can work on reader macros too!
(hissp.._macro_.alias M: hissp.._macro_)
M:#!b"Read-time b# via alias."      ;Extra arg for alias with (!)

L# !1 !2 primary                    ;Note the order!
.#(en#list "primary" 1 2)           ;Inject. Note the order.

!1                                  ;! is for a single Extra.
hissp.reader..Extra#(: :? 0 :* (1 2 3)) ; but Extra can have multiple elements.
!!!1 2 3                            ;Extras can have extras.

L#!: !:* !(0 1 2) !:? !3 primary    ;Unpacking works like calls.
L#!0 !: !:* !(1 2 3)primary         ;Same effect.
L#hissp.reader..Extra#(0 : :* (1 2 3))primary ;Same effect.

(setattr _macro_ 'E\# hissp.reader..Extra)

L# !0 E#(1 2) !3 primary            ;Same effect.
L#E#(0 : :* (1 2 3))primary         ;Same effect.

;; Kwargs also work like calls.
builtins..dict#()
builtins..dict#!: !spam !1  !foo !2  !:** !.#(dict : eggs 3  bar 4)()
builtins..dict#E#(: spam 1  foo 2  :** .#(dict : eggs 3  bar 4))()
builtins..dict#!: !!spam 1 !!foo 2 !!:** .#(dict : eggs 3  bar 4)()

;; Yeah, you can nest these if you have to.
L# !x
   !L# !1 L# !A
          inner
   !y
outer

;; The compiler will evaluate tuples no matter how the reader produces them.
builtins..tuple#L# !"Hello" !"World!" print