Lissp Quick Start

(Outputs hidden for brevity.)
;;;; Lissp Quick Start

"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, demonstrating Lissp's (and
thereby Hissp's) features 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, read the Hissp tutorial.

Some examples depend on state set by previous examples to work.
Prerequisites for examples not in the same section are marked with
'/!\'. Don't skip these! Re-enter them if you start a new session.
"

;;;; Installation

;; These docs are for version 0.3.0
;; Install the matching Hissp version with
;; $ pip install hissp==0.3.0
;; Start the REPL with
;; $ lissp
;; You can quit with EOF or (exit).

;;;; Simple Atoms

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

;;; Singleton

None
...                                 ;Ellipsis

;;; Boolean

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

;;; Integer

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

;;; Floating-Point

3.
-4.2
4e2
-1.6e-2

;;; Complex

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

;;;; Simple Tuples

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

;;;; Symbolic Atoms

;;; Identifiers

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

;;; Imports

math.                               ;Module literals import!
math..tau                           ;Qualified identifier. Attribute of a module.
collections.abc.                    ;Submodule literal. Has package name.

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

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

;;;; String Atoms

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

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

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

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

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

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

;;; Operators

;; Hissp is simpler than Python. No operators! Use calls instead.

(operator..add 40 2)
(.update (globals) : + operator..add) ;/!\ Assignment. Identifier munged.
(+ 40 2)                            ;No operators. This is still a function call!

;;;; 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")

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

;;; Control Flow

;; Hissp is simpler than Python. No control flow! Use higher-order functions instead.

(any (map (lambda (c) (print c))      ;Loops!
          "abc"))

((.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 to implement a ternary.

(.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)))

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

;;;; Advanced Lambdas

;; Python parameter types are rather involved. Lambda does all of them.
;; Like calls, they are all paired. :? 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.

;;;; 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, but it would crash, because
;; ints are not callable in Python.

;; 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")                  ;Unexpected? "..."/#"..." 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 literals 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.

;;;; Simple Reader Macros

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

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

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

;; Qualification prevents accidental name collisions in
;; programmatically generated code. But qualification doesn't work on
;; local variables, which can't be imported. For these, we use a template
;; counter suffix instead of a qualifier to ensure a variable can only
;; be used in the same template it was defined in. The gensym reader
;; macro ($#) generates a symbol with the current template's count.
`($#eggs $#spam $#bacon $#spam)     ;Generated symbols for macro hygiene.
`$#spam                             ;Template count in name prevents collisions.

;;;; 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 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.basic.._macro_.define)

;; An invocation qualified with _macro_ is a macro invocation.
(hissp.basic.._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.basic.._macro_ 'SPAM '"eggs") ;Method syntax is never macro invocation.

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


(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, gensyms are an alternative to qualification for locals.
;; (Thus, gensyms are never auto-qualified by templates.)
(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 creates these for symbols in the invocation position when
;; they can't tell if _macro_ would work. The compiler skips QzMaybe_
;; unless it can resolve the symbol with QzMaybe_ as _macro_.
`(+ 1 2 3 4)

;; 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 : :* args)
           (.__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)

(setattr _macro_
         '*
         (lambda (first : :* args)
           (.__getitem__
             `(,first
               (operator..mul ,first (* ,@args)))
             (bool args))))
(* 1 2 3 4)

;; 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 discarded the qualifier
;; on sep, because it's a kwarg.
(p123 :)

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

;;;; The Basic Macros

;; To make the REPL more usable, it comes with some basic macros already
;; defined. Their design has been deliberately restricted so that their
;; compiled output does not require the Hissp package to be installed to
;; work. While these may suffice for small or embedded Hissp projects,
;; you will probably want a more capable macro suite (such as Hebigo's)
;; for general use. You are not required to use the basic macros at all,
;; so by default, they don't work in .lissp files unqualified. They're
;; available qualified from hissp.basic.._macro_.

;;; Side Effect

(print (prog1 0                     ;Sequence for side effects, eval to first.
         (print 1)
         (print 2)))

(print (progn (print 1)             ;Sequence for side effects, eval to last.
              (print 2)
              3))

(prog1                              ;Sequence for side effects, eval to first.
  (progn (print 1)                  ;Sequence for side effects, eval to last.
         3)
  (print 2))

;;; Definition

(deftype Point2D (tuple)
  __doc__ "Simple ordered pair."
  __new__ (lambda (cls x y)
            (.__new__ tuple cls `(,x ,y)))
  __repr__ (lambda (self)
             (.format "Point2D({!r}, {!r})" : :* self)))
(Point2D 1 2)

;; Define a function in the _macro_ namespace.
;; Creates the _macro_ namespace if absent.
;; Can also have a docstring.
(defmacro p123 (sep)
  "Prints 1 2 3 with the given separator"
  `(print 1 2 3 : sep ,sep))

(help _macro_.p123)

(define SPAM "tomato")              ;We've seen this one already.
SPAM

(let (x "a"                         ;Create locals.
      y "b")                        ;Any number of pairs.
  (print x y)
  (let (x "x"
        y (+ x x))                  ;Not in scope until body.
    (print x y))                    ;Outer variables shadowed.
  (print x y))                      ;Inner went out of scope.

;;; Configuration

(attach (types..SimpleNamespace) + : a 1  b "Hi")
(doto []
  (.extend "bar")
  (.sort)
  (.append "foo"))

;;; Threading

(-> "world!"                        ;Thread-first
    (.title)
    (->> (print "Hello")))          ;Thread-last
(help _macro_.->)
(help _macro_.->>)

;;; The Basic Prelude

;; An inline convenience micro-prelude for Hissp.
;; Imports partial and reduce; star imports from operator and
;; itertools; defines the en- group utilities; and imports a copy of
;; hissp.basic.._macro_ (if available). Usually the first form in a file,
;; because it overwrites _macro_, but completely optional.
;; Implied for $ lissp -c commands.
(prelude)                           ;/!\ Or (hissp.basic.._macro_.prelude)

;;; Control Flow

;; Hissp has no control flow, but you can build them with macros.

(any-for i (range 1 11)             ;Imperative loop with break.
  (print i : end " ")
  (not_ (mod i 7)))
;; 1 2 3 4 5 6 7 True

(if-else (eq (input "? ") 't)          ;ternary conditional
  (print "Yes")
  (print "No"))

(let (x (float (input "? ")))
  ;; Multi-way branch.
  (cond (lt x 0) (print "Negative")
        (eq x 0) (print "Zero")
        (gt x 0) (print "Positive")
        :else (print "Not a number"))
  (when (eq x 0)                       ;Conditional with side-effects & no alternative.
    (print "In when")
    (print "was zero"))
  (unless (eq x 0)
    (print "In unless")
    (print "wasn't zero")))

;; Shortcutting logical and.
(&& True True False)
(&& False (print "oops"))
(&& True 42)

;; Shortcutting logical or.
(|| True (print "oops"))
(|| 42 False)

;;; Obligatory Factorial III

;; With the prelude, we can define a nicer-looking version.
(define factorial-III
  (lambda i
    (if-else (le i 1)
      1
      (mul i (factorial-III (sub i 1))))))
(factorial-III 7)

;;;; The En- Group

;; These are small utility functions defined by the basic prelude.
;; Most of them put their arguments into a collection, hence the en-.
(entuple 1 2 3)
(enlist 1 2 3)
(enset 1 2 3)

;; From [en]- [fro]zen [s]e[t], because "enfrozenset" is too long.
(enfrost 1 2 3)

;; Unlike (dict) with kwargs, keys need not be identifiers.
(endict 1 2  3 4)                   ;Note the implied pairs.

;; The need for endict is apparent, considering alternatives.
(dict (enlist (entuple 1 2) (entuple 3 4)))

;; Converts to str and joins. Usually .format is good enough, but
;; sometimes you need interpolations inline, like f-strings. Don't forget
;; the format builtin can apply formatting specs.
(enstr "<p>"(format 40 ".2f")" + "(add 1 1)"</p>")

;; OK, so this one's not a collection. Guards against the targeted exception classes.
(engarde (entuple FloatingPointError ZeroDivisionError)          ;two targets
         (lambda e (print "Oops!") e)                            ;handler (returns exception)
         truediv 6 0)                                            ;calls it on your behalf

(engarde ArithmeticError repr truediv 6 0)                       ;superclass target
(engarde ArithmeticError repr truediv 6 2)                       ;returned answer

;; You can nest them.
(engarde Exception                                               ;The outer engarde
  print
  engarde ZeroDivisionError                                      ; calls the inner.
  (lambda e (print "It means what you want it to mean."))
  truediv "6" 0)                                                 ;Try variations.

;;;; Advanced Reader Macros

;;; 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 _#.
"
(print 1 _#(I'm not here!) 2 3)

;;; Qualified Reader Macros

;; Invoke any qualified callable on the next parsed object at read time.
builtins..hex#3840                  ;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_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

;;; 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 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 there first.
"
'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.

;;;; The Basic Reader Macros

b#"bytes"                           ;Bytes reader macro.
b'bytes'                            ;NameError about 'bQzAPOS_bytesQzAPOS_'

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

(help _macro_.b\#)                  ;Unqualified reader macros live in _macro_ too.

;; The en- reader macro.
(en#list 1 2 3)                     ;Like enlist.
(en#.extend _ 4 5 6)                ;Methods too.
_

(en#collections..deque 1 2 3)       ;Generalizes to any function of 1 iterable.

;; Not technically a basic reader macro, but a basic macro for defining them.
;; Alias makes a new reader macro to abbreviate a qualifier.
;; This is an alternative to adding an import to _macro_ or globals.
(hissp.basic.._macro_.alias M: hissp.basic.._macro_)
'M:#alias                           ;Now short for 'hissp.basic.._macro_.alias'.
M:#b\#                              ;b# macro callable
(M:#b\# "b# macro at compile time")
hissp.basic.._macro_.b\##"Fully qualified b# macro at read time."

;; Comment string.
<<#;Don't worry about the "quotes".

;;; Aside: Extra (!), the Final Builtin Reader Macro

_#"Reader macros take one primary argument, but additional arguments
can be passed in with the extra macro !. A reader macro consumes the
next parsed object, and if it's an Extra, consumes one again. Thus,
extras must be written between the # and primary argument, but because
they're often optional refinements, which are easier to define as
trailing optional parameters in in Python functions, they get passed
in after the primary argument.
"
(setattr _macro_ 'L\# enlist)

L#primary
L#!1 primary

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

L# !1 !2 primary                    ;Note the order!
.#(enlist "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. They stack.

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_ 'X\# hissp.reader..Extra)

L# !0 X#(1 2) !3 primary            ;Same effect.
L#X#(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#X#(: 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

;;; Joined Comment String

<<#!;C:\bin
   !;C:\Users\ME\Documents
   !;C:\Users\ME\Pictures
";"

;; Embed other languages without escapes.
(exec
  <<#
  !;for i in 'abc':
  !;    for j in 'xyz':
  !;        print(i+j, end=" ")
  !;print('.')
  !;
  #"\n")

;;;; Collections

;;; Templates and Tuples

'(1 2 3)                            ;tuple
`(,(pow 42 0) ,(+ 1 1) 3)           ;Interpolate with templates.
`("a" 'b c ,'d ,"e")                ;These can be tricky. Careful.
'(1 "a")                            ;Recursive quoting.
'(1 .#"a")                          ;Injected Hissp-level string.
`(1 ,"a")                           ;Interpolated string.

;; Helper functions may be easier than templates for data.
(entuple 0 "a" 'b :c)
(en#tuple 0 "a" 'b :c)

;;; Other Collection Types

(list `(1 ,(+ 1 1) 3))
(set '(1 2 3))

(bytes '(98 121 116 101 115))
(bytes.fromhex "6279746573")
;; Read-time equivalents.
builtins..bytes.fromhex#.#"6279746573"
builtins..bytes#(98 121 116 101 115)
.#"b'bytes'"                        ;bytes literal Python injection

(dict : + 0  a 1  b 2)              ;Symbol keys are easy. The common case.
(.__getitem__ _ '+)
(dict (zip '(1 2 3) "abc"))         ;Non-symbol keys are possible.
(dict '((a 1) (2 b)))               ;Mixed key types. Beware of quoting strings.
(dict `((,'+ 42)
        (,(+ 1 1) ,'b)))            ;Run-time interpolation with a template.
(.__getitem__ _ '+)

(endict 1 2  'a 'b)

;;; Collection Atoms

.#"[]"                              ;List from a Python injection.
.#[]                                ;You can drop the quotes sometimes.
[]                                  ; And the reader macro!

[1,2,3]                             ;List/set/dict atoms are a kind of injection.
{1,2,3}                             ; They read in as a single atom, so have
{'a':1,2:b'b'}                      ; compile-time literals only--No interpolation!
[1,{2},{3:[4,5]},'six']             ;Nesting is allowed.

;; Collection atoms are a convenience for simple cases only.
.#"['1 2','3',(4,5),R'6;7\8']"
;; After dropping quotes, these tokenize like other atoms, so you need escapes.
['1\ 2',\"3\",\(4,5\),R'6\;7\\8']   ;Not so convenient now. Simple cases only!

;; Constructors or helpers also work. (And can interpolate run-time data.)
(list `(,"1 2" ,"3" (4 5) ,"6;7\8"))
(enlist "1 2" "3" '(4 5) "6;7\8")

_#"Even though they evaluate the same, there's a subtle compile-time difference
between a collection atom and a string injection. This can matter because
macros get all their arguments unevaluated.
"

'[1,'''2\ 3''']                     ;[1, '2 3']
'.#"[1,'''2 3''']"                  ;"[1,'''2 3''']"

;; But you can still get a real collection at compile time.
'.#(eval "[1,'''2 3''']")           ;[1, '2 3']
'.#.#"[1,'''2 3''']"                ;[1, '2 3']

(lambda ['a','b','c'])              ;I don't recommend this, but it works.
(lambda .#"['a','b','c']")          ;Oops.
(lambda .#.#"['a','b','c']")        ;Another inject fixes it.

'(lambda ['a','b','c'])             ;Params is a list.
'(lambda .#"['a','b','c']")         ;Params is a string.
'(lambda .#.#"['a','b','c']")       ;Params is a list.

(lambda "abc")                      ;Oops.
(lambda .#"abc")                    ;Inject fixes it.

'(lambda "abc")                     ;See why? Extra characters.
'(lambda .#"abc")                   ;Evaluated object.

(lambda abc)                        ;Compare to using a symbol.
'(lambda abc)