Lissp Quick Start

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

"Lissp is a lightweight text language representing the Hissp data-
structure language. The Lissp reader converts Lissp's symbolic
expressions to Hissp's syntax trees. The Hissp compiler then translates
Hissp to a functional subset of Python.

This document is written like a .lissp file, demonstrating Lissp's (and
thereby Hissp's) features with minimal exposition. Some familiarity with
Python is assumed. Familiarity with another Lisp dialect is not assumed,
but helpful. See the Hissp tutorial for more detailed explanations.

To fully understand these examples, you must see their output. 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.

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

;;;; Installation

;; Install Hissp with
;; $ pip install hissp==0.2.0
;; Start the REPL with
;; $ lissp
;; You can quit with EOF or (exit).

;;;; Atoms

;;; Singleton

None
...                                    ;Ellipsis

;;; Boolean

False                                  ;0
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!

;;;; Symbolic

object                                 ;Normal identifier.
object.__class__                       ;Attribute identifier with dot, as Python.

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.
object.__class__.__name__              ;Attributes chain.
collections.abc..Sequence.__class__.__name__ ;All together now.

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

'+                                     ;Read-time munging of invalid identifiers.
'Also-a-symbol!                        ;Alias for 'AlsoxH_axH_symbolxBANG_
'𝐀                                     ;Alias for 'A (munges to unicode normal form KC)
'->>
:->>                                   ;These don't represent identifiers, don't munge.

'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

"raw string"
'not-string'                           ;symbol
#"Say \"Cheese!\" \u263a"              ;Hash strings use Python escapes.

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

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

;;;; Calls

(print :)                              ;Paren before function! Note the colon.
(print : :? 1  :? 2  :? 3  sep "-")    ;Arguments pair with a parameter name. No commas!
(print 1 2 3 : sep "-")                ;Arguments left of the : implicitly pair with :?.
(print 1 : :* "abc"  :? 2  :** (dict : sep "-")) ;Unpacking!
(print "Hello, World!")                ;No : is the same as putting it last.
(print "Hello, World!" :)              ;Compare.

(.upper "shout!")                      ;Method calls require 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 is still available.

;;;; Lambda

;; Lambda is one of only two special forms--looks like a call, but isn't.

;; Python parameter types are rather involved. Lambda does all of them.
(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 returns empty tuple if body is empty.)
  (print (globals))
  (print (locals))                     ;side effects
  b)                                   ;last value is returned

;; Parameters left of the : are paired with placeholder (:?), parallels calls.
(lambda (: :* a))                      ;Star arg must pair with star, as Python.
(lambda (:* a))                        ;Kwonly! Not star arg! Final : implied.
(lambda (:* a :))                      ;Compare.
(lambda (: :* :?  a :?))
(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                           ; parameters are not strictly required to be a tuple.
   (print c b a))                      ;There are three parameters.
 3 2 1)

(lambda (:))                           ;Explicit : is still allowed with no parameters.
(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)
(.__setitem__ (globals) '+ operator..add) ;(!) Assignment. Symbols munge.
(+ 40 2)                               ;No operators. This is still a function call!

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

;; Don't worry, macros make this much easier.

;;;; Quote

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

;; Quotation prevents evaluation.
;; Treating the code itself as data is the key concept in metaprogramming.

(quote (print 1 2 3 : sep "-"))        ;Just a tuple.
(quote identifier)                     ;Just a string.
(quote 42)                             ;Just a number. It was before though.
(quote "string")                       ;Not what you expected? Eval it.
(eval (quote "string"))                ;It's a string of Python code. For a string.

:?                                     ;Just a string?
((lambda (: a :?) a))                  ;Not that simple!
((lambda (: a (quote :?)) a))          ;Just a string.

;;;; Reader Macros

'x                                     ;Same as (quote x). Symbols are just quoted identifiers!
'(print "Hi")                          ;Reveal the Hissp.

;; Reader macros are metaprograms to abbreviate Hissp instead of representing it directly.

;;; Template Quote

;; (Like quasiquote, backquote, or syntax-quote from other Lisps.)

`print                                 ;Automatic qualification!
`foo                                   ;Compare.

`(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                                 ;Interpolations not auto-qualified!
`(print ,@"abc")                       ;Splice unquote (,@) interpolates and unpacks.
`(print ,@(.upper "abc"))
`($#eggs $#spam $#bacon $#spam)        ;Generated symbols for macros.
`$#spam                                ;Gensym counter prevents name collisions.

_#"
The discard reader macro _# omits the next form.
It's a way to comment out code structurally.
It can also make comments like this one.
This would show up when compiled if not for _#.
"
(print 1 _#(I'm not here!) 2 3)

;; Invoke any importable unary callable at read time.
builtins..float#inf                    ;Extensible literals!

;; Reader macros compose. Note the quote.
'hissp.munger..demunge#xH_xGT_xGT_
''x
'\'x

(print (.upper 'textwrap..dedent##"\
               These lines
               Don't interrupt
               the flow."))

;; The "inject" reader macro evaluates the next form
;; and puts the result directly in the Hissp.
.#(fractions..Fraction 1 2)            ;Fraction() is multiary.

;; Use a string to inject Python into the compiled output.
(lambda (a b c)
  ;; Hissp may not have operators, but Python does.
  .#"(-b + (b**2 - 4*a*c)**0.5)/(2*a)")

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

;;;; Collections

;;; Templates and Tuples

'(1 2 3)                               ;tuple
`(,(pow 42 0) ,(+ 1 1) 3)              ;Interpolate with templates.
`("a" 'b c ,'d ,"e")                   ;Remember what happens when you quote strings?
'(1 "a")                               ;Recursive quoting.
`(1 ,"a")

;; Helper functions may be easier than templates.
((lambda (: :* xs) xs) 0 "a" 'b :c)
(.__setitem__ (globals) 'entuple (lambda (: :* xs) xs))
(entuple 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")
.#"b'bytes'"                           ;bytes literal Python injection

(dict : + 0  a 1  b 2)                 ;Symbol keys are easy. The common case.
(.__getitem__ _ '+)                    ;In the REPL, _ is the last result that wasn't None.
(dict (zip '(1 2 3) "abc"))            ;Non-symbol keys are possible.
(dict '((a 1) (2 b)))                  ;Mixed key types. Beware of strings.
(dict `((,'+ 42)
        (,(+ 1 1) ,'b)))               ;Runtime interpolation with a template.
(.__getitem__ _ '+)

(.__setitem__ (globals)
              'endict                  ;dict helper function
              (lambda (: :* pairs)
                ;; Injections work on any Python expression, even comprehensions!
                .#"{k: next(it) for it in [iter(pairs)] for k in it}"))
(endict 1 2  'a 'b)

;;; Collection Atoms

.#"[]"                                 ;List from a Python injection.
.#[]                                   ;As a convenience, you can drop the quotes in some cases.
[]                                     ; And the reader macro!

[1,2,3]                                ;List, set, and dict atoms are a special case
{1,2,3}                                ; of Python injection. They read in as a single atom, so
{'a':1,2:b'b'}                         ; they have 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 runtime data.)
(list `(,"1 2" ,"3" (4 5) ,"6;7\8"))

(.__setitem__ (globals) 'enlist (lambda (: :* xs) (list xs))) ;helper function
(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. Compare.
(lambda .#.#"['a','b','c']")           ;Another inject fixes it.
(lambda "abc")                         ;Oops.
(lambda .#"abc")                       ;Inject fixes it.
(lambda abc)                           ;Identifiers are also a special case of injection!

;;;; Compiler Macros

_#"Macroexpansion happens at compile time, after the reader, so macros also
work in readerless mode, or with alternative Hissp readers other than Lissp.
Macros get all of their arguments unevaluated and the compiler
inserts the resulting Hissp into that point in the program.
Like special forms, macro invocations look like function calls, but aren't."

;; An invocation using an identifier 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.
(.define hissp.basic.._macro_ 'SPAM '"eggs") ;Method syntax is never 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_)
(help _macro_.define)

;; Unqualified macro invocations really look like function calls, but aren't.
(define EGGS "spam")
EGGS

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

;; Maybe the expanded code could only run it once?
(setattr _macro_
         'oops-triple
         (lambda x
           `((lambda (: x ,x)          ;Expand to lambda to make a local variable.
               (+ x (+ x x))))))
(oops-triple 14)                       ;Don't forget that templates qualify symbols!

;; If you didn't want it qualified, that's a sign you should use a gensym instead:
(setattr _macro_
         'once-triple
         (lambda x
           `((lambda (: $#x ,x)
               (+ $#x (+ $#x $#x))))))
(once-triple (loud-number 14))

;; Sometimes you really want a name captured, so don't qualify and don't generate a new symbol:
(setattr _macro_
         'fnx
         (lambda (: :* body)
           `(lambda (,'X)              ;,'X instead of $#X
              (,@body))))
(list (map (fnx mul X X) (range 6)))   ;Shorter lambda! Don't nest them.

;; Recursive macro. (Multiary +)
(setattr _macro_
         '+
          (lambda (first : :* args)
            (.__getitem__
              `(,first (add ,first (+ ,@args)))
              (bool args))))
(+ 1 2 3 4)

(setattr _macro_
         '*
          (lambda (first : :* args)
            (.__getitem__
              `(,first (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.
                   '(1 2 3 4))

;; 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 xPLUS_, but not xSTAR_.
(dir _macro_)                          ;Has both.

;; ``$ 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 and compile them to spam.py & eggs.py
(os..system #"echo (print \"Hello World!\") > eggs.lissp")
(os..system #"echo (print \"Hello from spam!\") (.__setitem__ (globals) 'x 42) > spam.lissp")
(hissp.reader..transpile __package__ 'spam 'eggs)

spam..x                                ;Side effects happen upon both compilation and import!
;; Hello from spam!
;; 42

spam..x                                ;42
eggs.                                  ;Hello, World!

;;;; Basic Macros

_#" The REPL comes with some basic macros defined in hissp.basic. By default,
they don't work in .lissp files unqualified. The compiled output from these
does not require hissp to be installed."

(help _macro_.->>)                     ;Macros have docstrings and live in _macro_.

;; Makes a new reader macro to abbreviate a qualifier.
(hissp.basic.._macro_.alias b/ hissp.basic.._macro_.)
'b/#alias                              ;Now short for 'hissp.basic.._macro_.alias'.

;; Imports a copy of hissp.basic.._macro_ (if available)
;; and star imports from operator and itertools.
(b/#prelude)

;;; Reader

b#"bytes"                               ;Bytes reader macro.
b'bytes'                                ;NameError: name 'bx1QUOTE_bytesx1QUOTE_' is not defined

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

;;; Side Effect

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

;;; Definition

(define answer 42)                     ;Add a global.
(deftype Point2D (tuple)
  __doc__ "Simple pair."
  __new__ (lambda (cls x y)
            (.__new__ tuple cls `(,x ,y))))
(Point2D 1 2)                          ;(1, 2)

;; Define a function in the _macro_ namespace.
;; Creates the _macro_ namespace if absent.
(defmacro triple (x)
  `(+ ,x ,x ,x))

(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))
  (print x y))

;;; Configuration

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

;;; Threading

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

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

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