API reference ************* This chapter describes most of Hy's public-facing macros, functions, and classes. It refers to Python's own documentation when appropriate rather than recapitulating the details of Python semantics. Contents ^^^^^^^^ * Core macros * Fundamentals * Quoting * Assignment, mutation, and annotation * Subsetting * Conditionals and basic loops * Comprehensions * Context managers and pattern-matching * Exception-handling * Functions * Macros * Classes * Modules * Miscellany * Placeholder macros * Hy * Readers * Python operators Core macros =========== The following macros are automatically imported into all Hy modules as their base names, such that "hy.core.macros.foo" can be called as just "foo". Macros that are also available as functions are described as functions under Python operators. Fundamentals ------------ macro(do(#* body)) "do" (called "progn" in some Lisps) takes any number of forms, evaluates them, and returns the value of the last one, or "None" if no forms were provided. (+ 1 (do (setv x (+ 1 1)) x)) ; => 3 macro(do-mac(#* body)) "do-mac" evaluates its arguments (in order) at compile time, and leaves behind the value of the last argument ("None" if no arguments were provided) as code to be run. The effect is similar to defining and then immediately calling a nullary macro, hence the name, which stands for "do macro". (do-mac `(setv ~(hy.models.Symbol (* "x" 5)) "foo")) ; Expands to: (setv xxxxx "foo") (print xxxxx) ; => "foo" Contrast with "eval-and-compile", which evaluates the same code at compile-time and run-time, instead of using the result of the compile-time run as code for run-time. "do-mac" is also similar to Common Lisp's SHARPSIGN DOT syntax ("#."), from which it differs by evaluating at compile-time rather than read-time. macro(eval-and-compile(#* body)) "eval-and-compile" takes any number of forms as arguments. The input forms are evaluated as soon as the "eval-and-compile" form is compiled, then left in the program so they can be executed at run- time as usual; contrast with "eval-when-compile". So, if you compile and immediately execute a program (as calling "hy foo.hy" does when "foo.hy" doesn't have an up-to-date byte-compiled version), "eval-and-compile" forms will be evaluated twice. For example, the following program (eval-when-compile (print "Compiling")) (print "Running") (eval-and-compile (print "Hi")) prints Compiling Hi Running Hi The return value of "eval-and-compile" is its final argument, as for "do". One possible use of "eval-and-compile" is to make a function available both at compile-time (so a macro can call it while expanding) and run-time (so it can be called like any other function): (eval-and-compile (defn add [x y] (+ x y))) (defmacro m [x] (add x 2)) (print (m 3)) ; prints 5 (print (add 3 6)) ; prints 9 Had the "defn" not been wrapped in "eval-and-compile", "m" wouldn't be able to call "add", because when the compiler was expanding "(m 3)", "add" wouldn't exist yet. While "eval-and-compile" executes the same code at both compile- time and run-time, bear in mind that the same code can have different meanings in the two contexts. Consider, for example, issues of scoping: (eval-when-compile (print "Compiling")) (print "Running") (eval-and-compile (setv x 1)) (defn f [] (setv x 2) (eval-and-compile (setv x 3)) (print "local x =" x)) (f) (eval-and-compile (print "global x =" x)) The form "(setv x 3)" above refers to the global "x" at compile- time, but the local "x" at run-time, so the result is: Compiling global x = 3 Running local x = 3 global x = 1 macro(eval-when-compile(#* body)) "eval-when-compile" executes the given forms at compile-time, but discards them at run-time and simply returns "None" instead; contrast "eval-and-compile". Hence, while "eval-when-compile" doesn't directly contribute code to the final program, it can change Hy's state while compiling, as by defining a function: (eval-when-compile (defn add [x y] (+ x y))) (defmacro m [x] (add x 2)) (print (m 3)) ; prints 5 (print (add 3 6)) ; raises NameError: name 'add' is not defined macro(py(string)) "py" parses the given Python code at compile-time and inserts the result into the generated abstract syntax tree. Thus, you can mix Python code into a Hy program. Only a Python expression is allowed, not statements; use "pys" if you want to use Python statements. The value of the expression is returned from the "py" form. (print "A result from Python:" (py "'hello' + 'world'")) The code must be given as a single string literal, but you can still use macros, "hy.eval", and related tools to construct the "py" form. If having to backslash-escape internal double quotes is getting you down, try a bracket string. If you want to evaluate some Python code that's only defined at run-time, try the standard Python function "eval()". The code is implicitly wrapped in parentheses so Python won't give you grief about indentation. After all, Python's indentation rules are only useful for grouping statements, whereas "py" only allows an expression. Python code need not syntactically round-trip if you use hy2py on a Hy program that uses "py" or "pys". For example, comments will be removed. macro(pys(string)) As "py", but the code can consist of zero or more statements, including compound statements such as "for" and "def". "pys" always returns "None". (pys "myvar = 5") (print "myvar is" myvar) Unlike "py", no parentheses are added, because Python doesn't allow statements to be parenthesized. Instead, the code string is dedented with "textwrap.dedent()" before parsing. Thus you can indent the code to match the surrounding Hy code when Python would otherwise forbid this, but beware that significant leading whitespace in embedded string literals will be removed. macro(pragma(#* args)) "pragma" is used to adjust the state of the compiler. It's called for its side-effects, and returns "None". The arguments are key- value pairs, like a function call with keyword arguments: (pragma :prag1 value1 :prag2 (get-value2)) Each key is a literal keyword giving the name of a pragma. Each value is an arbitrary form, which is evaluated as ordinary Hy code but at compile-time. The effect of each pragma is locally scoped to its containing function, class, or comprehension form (other than "for"), if there is one. These pragmata are currently implemented: * ":hy": Set this to a string giving a Hy version number or prefix thereof, such as "1.1.0" or "1", to raise a compile-time error if the currently executing version of Hy isn't at least this new. If you're writing a package, you should still declare the required version of Hy in "setup.py" or "pyproject.toml" or whatever, because "pip" won't look for "(pragma :hy …)" calls. In the future, this pragma may also switch on features of Hy that were introduced in or before the given version. * ":warn-on-core-shadow": If true (the default), "defmacro" and "require" will raise a warning at compile-time if you define a macro with the same name as a core macro. Shadowing a core macro in this fashion is dangerous, because other macros may call your new macro when they meant to refer to the core macro. Quoting ------- macro(quote(model)) Return the given model without evaluating it. Or to be more pedantic, "quote" complies to code that produces and returns the model it was originally called on. Thus "quote" serves as syntactic sugar for model constructors: (quote a) ; Equivalent to: (hy.models.Symbol "a") (quote (+ 1 1)) ; Equivalent to: (hy.models.Expression [ ; (hy.models.Symbol "+") ; (hy.models.Integer 1) ; (hy.models.Integer 1)]) "quote" itself is conveniently abbreviated as the single-quote character "'", which needs no parentheses, allowing one to instead write: 'a '(+ 1 1) See also: * "quasiquote" to substitute values into a quoted form * "hy.eval" to evaluate models as code * "hy.repr" to stringify models into Hy source text that uses "'" macro(quasiquote(model)) macro(unquote(model)) macro(unquote-splice(model)) "quasiquote" is like "quote" except that it treats the model as a template, in which certain special expressions indicate that some code should be evaluated and its value substituted there. The idea is similar to C's "sprintf" or Python's various string-formatting constructs. For example: (setv x 2) (quasiquote (+ 1 (unquote x))) ; => '(+ 1 2) "unquote" indicates code to be evaluated, so "x" becomes "2" and the "2" gets inserted in the parent model. "quasiquote" can be abbreviated as a backtick (`), with no parentheses, and likewise "unquote" can be abbreviated as a tilde ("~"), so one can instead write simply `(+ 1 ~x) (In the bulk of Lisp tradition, unquotation is written ",". Hy goes with Clojure's choice of "~", which has the advantage of being more visible in most programming fonts.) Quasiquotation is convenient for writing macros: (defmacro set-foo [value] `(setv foo ~value)) (set-foo (+ 1 2 3)) (print foo) ; => 6 Another kind of unquotation operator, "unquote-splice", abbreviated "~@", is analogous to "unpack-iterable" in that it splices an iterable object into the sequence of the parent sequential model. Compare the effects of "unquote" to "unquote-splice": (setv X [1 2 3]) (hy.repr `[a b ~X c d ~@X e f]) ; => '[a b [1 2 3] c d 1 2 3 e f] If "unquote-splice" is given any sort of false value (such as "None"), it's treated as an empty list. To be precise, "~@x" splices in the result of "(or x [])". Note that while a symbol name can begin with "@" in Hy, "~@" takes precedence in the parser, so if you want to unquote the symbol "@foo" with "~", you must use whitespace to separate "~" and "@", as in "~ @foo". Assignment, mutation, and annotation ------------------------------------ macro(setv(#* args)) "setv" compiles to an *assignment statement* (see "setx" for assignment expressions), which sets the value of a variable or some other assignable expression. It requires an even number of arguments, and always returns "None". The most common case is two arguments, where the first is a symbol: (setv websites 103) (print websites) ; => 103 Additional pairs of arguments are equivalent to several two- argument "setv" calls, in the given order. Thus, the semantics are like Common Lisp's "setf" rather than "psetf". (setv x 1 y x x 2) (print x y) ; => 2 1 All the same kinds of complex assignment targets are allowed as in Python. So, you can use list assignment to assign in parallel. (As in Python, tuple and list syntax are equivalent for this purpose; Hy differs from Python merely in that its list syntax is shorter than its tuple syntax.) (setv [x y] [y x]) ; Swaps the values of `x` and `y` Unpacking assignment looks like this (see "unpack-iterable"): (setv [letter1 letter2 #* others] "abcdefg") (print letter1 letter2 (hy.repr others)) ; => a b ["c" "d" "e" "f" "g"] Finally, as of Hy 1.2, you can precede an assignment pair with the keyword ":chain" to assign the same value multiple times to each of several targets. This construct compiles to a chained assignment in Python. (setv :chain [x y z] 0) (print x y z) ; => 0 0 0 See "let" to simulate more traditionally Lispy block-level scoping. macro(setx(target, value)) "setx" compiles to an assignment expression (**PEP 572**). Thus, unlike "setv", it returns the assigned value. It takes exactly two arguments, and the target must be a bare symbol. (when (> (setx x (+ 1 2)) 0) (print x "is greater than 0")) ; => 3 is greater than 0 macro(let(bindings, #* body)) "let" is a macro for simulating traditional block scoping as seen in other Lisps. Since it coexists with ordinary Python scoping, its consequences can be complex, so it's wise to get a solid understanding of Python scoping before you use it. Beginners to Python should note particularly that "setv" inside a function or class typically creates a local variable, so "let" isn't required for local variables or closures as it is in many other Lisps. That disclaimer aside, "let" creates local variables with lexically scoped names. The macro takes a list of binding pairs followed by a "body" which gets executed. A let-bound name ceases to refer to that local outside the "let" form, but arguments in nested functions, and bindings in nested "let" forms, can shadow these names. (let [x 5 y 6] ; Create `x` and `y` (print x y) ; => 5 6 (let [x 7] ; Create a variable that shadows the earlier `x` (print x y)) ; => 7 6 (print x y)) ; => 5 6 The left-hand item of a binding pair is typically a plain symbol, but it can also use extended iterable unpacking (**PEP 3132**): (let [[head #* tail] #(0 1 2)] [head tail]) ; => [0 [1 2]] Basic assignments, as with "setv" or "+=", will update the local variable named by a let binding when they assign to a let-bound name. But assignments via "import" are always hoisted to normal Python scope, and likewise, "defn" or "defclass" will assign the function or class in the Python scope, even if it shares the name of a let binding. To avoid this hoisting, use "importlib.import_module()", "fn", or "type" (or whatever metaclass) instead. If "lfor", "sfor", "dfor", or "gfor" (but not "for") is in the body of a "let", assignments in iteration clauses and ":setv" clauses will create a new variable in the comprehenion form's own scope, without touching any outer let-bound variable of the same name. Like the "let*" of many other Lisps, "let" executes the variable assignments one-by-one, in the order written: (let [x 5 y (+ x 1)] (print x y)) ; => 5 6 (let [x 1 x (fn [] x)] (x)) ; => 1 Note that let-bound variables continue to exist in the surrounding Python scope. As such, let-bound objects may not be eligible for garbage collection as soon as the "let" ends. To ensure there are no references to let-bound objects as soon as possible, use "del" at the end of the "let", or wrap the "let" in a function. macro(global(#* syms)) "global" compiles to a "global" statement, which declares one or more names as referring to global (i.e., module-level) variables. The arguments are symbols; with no arguments, "global" has no effect. The return value is always "None". (setv a 1 b 10) (print a b) ; => 1 10 (defn f [] (global a) (setv a 2 b 20)) (f) (print a b) ; => 2 10 macro(nonlocal(#* syms)) Similar to "global", but names can be declared in any enclosing scope. "nonlocal" compiles to a "global" statement for any names originally defined in the global scope, and a "nonlocal" statement for all other names. (setv a 1 b 1) (defn f [] (setv c 10 d 10) (defn g [] (nonlocal a c) (setv a 2 b 2 c 20 d 20)) (print a b c d) ; => 1 1 10 10 (g) (print a b c d)) ; => 2 1 20 10 (f) macro(del(#* args)) "del" compiles to a "del" statement, which deletes variables or other assignable expressions. It always returns "None". (del foo (get mydict "mykey") myobj.myattr) macro(annotate(value, type)) "annotate" and its shorthand form "#^" are used to denote annotations, including type hints, in three different contexts: * Standalone variable annotations (**PEP 526**) * Variable annotations in a "setv" call * Function-parameter annotations (**PEP 3107**) The difference between "annotate" and "#^" is that "annotate" requires parentheses and takes the name to be annotated first (like Python), whereas "#^" doesn't require parentheses (it only applies to the next two forms) and takes the name second: (setv (annotate x int) 1) (setv #^ int x 1) The order difference is not merely visual: "#^" actually evaluates the type first. Here are examples with "#^" for all the places you can use annotations: ; Annotate the variable `x` as an `int` (equivalent to `x: int`). #^ int x ; You can annotate with expressions (equivalent to `y: f(x)`). #^(f x) y ; Annotations with an assignment: each annotation `(int, str)` ; covers the term that immediately follows. ; Equivalent to `x: int = 1; y = 2; z: str = 3` (setv #^ int x 1 y 2 #^ str z 3) ; Annotate `a` as an `int`, `c` as an `int`, and `b` as a `str`. ; Equivalent to `def func(a: int, b: str = None, c: int = 1): ...` (defn func [#^ int a #^ str [b None] #^ int [c 1]] ...) ; Function return annotations come before the function name (if ; it exists). (defn #^ int add1 [#^ int x] (+ x 1)) (fn #^ int [#^ int y] (+ y 2)) For annotating items with generic types, the "of" macro will likely be of use. An issue with type annotations is that, as of this writing, we know of no Python type-checker that can work with "ast" objects or bytecode files. They all need Python source text. So you'll have to translate your Hy with hy2py in order to actually check the types. macro(deftype(args)) "deftype" compiles to a "type" statement, which defines a type alias. It requires Python 3.12. Its arguments optionally begin with ":tp" and a list of type parameters (as in "defn"), then specify the name for the new alias and its value. (deftype IntOrStr (| int str)) (deftype :tp [T] ListOrSet (| (get list T) (get set T))) Subsetting ---------- . The dot macro "." compiles to one or more *attribute references*, which select an attribute of an object. The first argument, which is required, can be an arbitrary form. With no further arguments, "." is a no-op. Additional symbol arguments are understood as a chain of attributes, so "(. foo bar)" compiles to "foo.bar", and "(. a b c d)" compiles to "a.b.c.d". As a convenience, "." supports two other kinds of arguments in place of a plain attribute. A parenthesized expression is understood as a method call: "(. foo (bar a b))" compiles to "foo.bar(a, b)". A bracketed form is understood as a subscript: "(. foo ["bar"])" compiles to "foo["bar"]". All these options can be mixed and matched in a single "." call, so (. a (b 1 2) c [d] [(e 3 4)]) compiles to a.b(1, 2).c[d][e(3, 4)] Dotted identifiers provide syntactic sugar for common uses of this macro. In particular, syntax like "foo.bar" ends up meaning the same thing in Hy as in Python. Also, "get" is another way to subscript in Hy. macro(unpack-iterable(form)) macro(unpack-mapping(form)) (Also known as the splat operator, star operator, argument expansion, argument explosion, argument gathering, and varargs, among others...) "unpack-iterable" and "unpack-mapping" allow an iterable or mapping object (respectively) to provide positional or keywords arguments (respectively) to a function. => (defn f [a b c d] [a b c d]) => (f (unpack-iterable [1 2]) (unpack-mapping {"c" 3 "d" 4})) [1 2 3 4] "unpack-iterable" is usually written with the shorthand "#*", and "unpack-mapping" with "#**". => (f #* [1 2] #** {"c" 3 "d" 4}) [1 2 3 4] Unpacking is allowed in a variety of contexts, and you can unpack more than once in one expression (**PEP 3132**, **PEP 448**). => (setv [a #* b c] [1 2 3 4 5]) => [a b c] [1 [2 3 4] 5] => [#* [1 2] #* [3 4]] [1 2 3 4] => {#** {1 2} #** {3 4}} {1 2 3 4} => (f #* [1] #* [2] #** {"c" 3} #** {"d" 4}) [1 2 3 4] Conditionals and basic loops ---------------------------- macro(if(test, true-value, false-value)) "if" compiles to an "if" expression (or compound "if" statement). The form "test" is evaluated and categorized as true or false according to "bool". If the result is true, "true-value" is evaluated and returned. Othewise, "false-value" is evaluated and returned. (if (has-money-left account) (print "Let's go shopping!") (print "Back to work.")) See also: * "do", to execute several forms as part of any of "if"'s three arguments. * "when", for shorthand for "(if condition (do …) None)". * "cond", for shorthand for nested "if" forms. macro(hy.core.macros.when(test, #* body)) Shorthand for "(if test (do …) None)". See "if". For a logically negated version, see Hyrule's "unless". (when panic (log.write panic) (print "Process returned:" panic.msg) (return panic)) macro(hy.core.macros.cond(#* args)) Shorthand for a nested sequence of "if" forms, like an "if"-"elif"-"else" ladder in Python. Syntax such as (cond condition1 result1 condition2 result2) is equivalent to (if condition1 result1 (if condition2 result2 None)) Notice that "None" is returned when no conditions match; use "True" as the final condition to change the fallback result. Use "do" to execute several forms as part of a single condition or result. With no arguments, "cond" returns "None". With an odd number of arguments, "cond" raises an error. macro(while(condition, #* body)) "while" compiles to a "while" statement, which executes some code as long as a condition is met. The first argument to "while" is the condition, and any remaining forms constitute the body. It always returns "None". (while True (print "Hello world!")) The last form of a "while" loop can be an "else" clause, which is executed after the loop terminates, unless it exited abnormally (e.g., with "break"). So, (setv x 2) (while x (print "In body") (-= x 1) (else (print "In else"))) prints In body In body In else If you put a "break" or "continue" form in the condition of a "while" loop, it will apply to the very same loop rather than an outer loop, even if execution is yet to ever reach the loop body. (Hy compiles a "while" loop with statements in its condition by rewriting it so that the condition is actually in the body.) So, (for [x [1]] (print "In outer loop") (while (do (print "In condition") (break) (print "This won't print.") True) (print "This won't print, either.")) (print "At end of outer loop")) prints In outer loop In condition At end of outer loop macro(break()) "break" compiles to a "break" statement, which terminates the enclosing loop. The following example has an infinite "while" loop that ends when the user enters "k": (while True (if (= (input "> ") "k") (break) (print "Try again"))) In a loop with multiple iteration clauses, such as "(for [x xs y ys] …)", "break" only breaks out of the innermost iteration, not the whole form. To jump out of the whole form, enclose it in a "block" and use "block-ret" instead of "break". In the case of "for", but not "lfor" and the other comprehension forms, you may also enclose it in a function and use "return". macro(continue()) "continue" compiles to a "continue" statement, which returns execution to the start of a loop. In the following example, "(.append output x)" is executed on each iteration, whereas "(.append evens x)" is only executed for even numbers. (setv output [] evens []) (for [x (range 10)] (.append output x) (when (% x 2) (continue)) (.append evens x)) In a loop with multiple iteration clauses, such as "(for [x xs y ys] …)", "continue" applies to the innermost iteration, not the whole form. To jump to the next step of an outer iteration, try rewriting your loop as multiple nested loops and interposing a "block", as in "(for [x xs] (block (for [y ys] …)))". You can then use "block-ret" in place of "continue". Comprehensions -------------- macro(for(#* args)) "for" compiles to one or more "for" statements, which execute code repeatedly for each element of an iterable object. The return values of the forms are discarded and the "for" form returns "None". (for [x [1 2 3]] (print "iterating") (print x)) ; Output: iterating 1 iterating 2 iterating 3 The first argument of "for", in square brackets, specifies how to loop. A simple and common case is "[variable values]", where "values" is an iterable object (such as a list) and "variable" is a symbol specifiying the name for each element. Subsequent arguments to "for" are body forms to be evaluated for each iteration of the loop. More generally, the first argument of "for" allows the same types of clauses as "lfor": (for [x [1 2 3] :if (!= x 2) y [7 8]] (print x y)) ; Output: 1 7 1 8 3 7 3 8 In particular, you can use an ":async" clause to get the equivalent of Python's "async for": (import asyncio) (defn :async numbers [] (yield 1) (yield 2)) (asyncio.run ((fn :async [] (for [:async x (numbers)] (print x))))) The last argument of "for" can be an "(else …)" form. This form is executed after the last iteration of the "for"'s outermost iteration clause, but only if that outermost loop terminates normally. If it's jumped out of with e.g. "break", the "else" is ignored. (for [x [1 2 3]] (print x) (when (= x 2) (break)) (else (print "loop finished"))) macro(lfor(#* args)) The comprehension forms "lfor", "sfor", "dfor", "gfor", and "for" are used to produce various kinds of loops, including Python-style *comprehensions*. "lfor" in particular can create a list comprehension. A simple use of "lfor" is: (lfor x (range 5) (* 2 x)) ; => [0 2 4 6 8] "x" is the name of a new variable, which is bound to each element of "(range 5)". Each such element in turn is used to evaluate the value form "(* 2 x)", and the results are accumulated into a list. Here's a more complex example: (lfor x (range 3) y (range 3) :if (!= x y) :setv total (+ x y) [x y total]) ; => [[0 1 1] [0 2 2] [1 0 1] [1 2 3] [2 0 2] [2 1 3]] When there are several iteration clauses (here, the pairs of forms "x (range 3)" and "y (range 3)"), the result works like a nested loop or Cartesian product: all combinations are considered in lexicographic order. The general form of "lfor" is: (lfor CLAUSES VALUE) where the "VALUE" is an arbitrary form that is evaluated to produce each element of the result list, and "CLAUSES" is any number of clauses. There are several types of clauses: * Iteration clauses, which look like "LVALUE ITERABLE". The "LVALUE" is usually just a symbol, but could be something more complicated, like "[x y]". * ":async LVALUE ITERABLE", which is an asynchronous form of iteration clause per Python's "async for". * ":do FORM", which simply evaluates the "FORM". If you use "(continue)" or "(break)" here, it will apply to the innermost iteration clause before the ":do". * ":setv LVALUE RVALUE", which is equivalent to ":do (setv LVALUE RVALUE)". * ":if CONDITION", which is equivalent to ":do (when (not CONDITION) (continue))". For "lfor", "sfor", "gfor", and "dfor", variables defined by an iteration clause or ":setv" are not visible outside the form. However, variables defined within the body, as with a "setx" expression, will be visible outside the form. In "for", by contrast, iteration and ":setv" clauses share the caller's scope and are visible outside the form. macro(dfor(#* args)) "dfor" creates a *dictionary comprehension*. Its syntax is the same as that of "lfor" except that it takes two trailing arguments. The first is a form producing the key of each dictionary element, and the second produces the value. Thus: (dfor x (range 5) x (* x 10)) ; => {0 0 1 10 2 20 3 30 4 40} macro(gfor(#* args)) "gfor" creates a *generator expression*. Its syntax is the same as that of "lfor". The difference is that "gfor" returns an iterator, which evaluates and yields values one at a time: (import itertools [count take-while]) (setv accum []) (list (take-while (fn [x] (< x 5)) (gfor x (count) :do (.append accum x) x))) ; => [0 1 2 3 4] accum ; => [0 1 2 3 4 5] macro(sfor(#* args)) "sfor" creates a *set comprehension*. "(sfor CLAUSES VALUE)" is equivalent to "(set (lfor CLAUSES VALUE))". See "lfor". Context managers and pattern-matching ------------------------------------- macro(with(managers, #* body)) "with" compiles to a "with" or an "async with" statement, which wraps some code with one or more *context managers*. The first argument is a bracketed list of context managers, and the remaining arguments are body forms. The manager list can't be empty. If it has only one item, that item is evaluated to obtain the context manager to use. If it has two, the first argument (a symbol) is bound to the result of the second. Thus, "(with [(f)] …)" compiles to "with f(): …" and "(with [x (f)] …)" compiles to "with f() as x: …". (with [o (open "file.txt" "rt")] (print (.read o))) If the manager list has more than two items, they're understood as variable-manager pairs; thus (with [v1 e1 v2 e2 v3 e3] ...) compiles to with e1 as v1, e2 as v2, e3 as v3: ... The symbol "_" is interpreted specially as a variable name in the manager list: instead of binding the context manager to the variable "_" (as Python's "with e1 as _: …"), "with" will leave it anonymous (as Python's "with e1: …"). Finally, any variable-manager pair may be preceded by the keyword ":async" to use an asynchronous context manager: (with [:async v1 e1] …) "with" returns the value of its last form, unless it suppresses an exception (because the context manager's "__exit__" method returned true), in which case it returns "None". So, the first example could also be written (print (with [o (open "file.txt" "rt")] (.read o))) macro(match(subject, #* cases)) "match" compiles to a *match statement*. It requires Python 3.10 or later. The first argument should be the subject, and any remaining arguments should be pairs of patterns and results. The "match" form returns the value of the corresponding result, or "None" if no case matched. (match (+ 1 1) 1 "one" 2 "two" 3 "three") ; => "two" You can use "do" to build a complex result form. Patterns, as in Python match statements, are interpreted specially and can't be arbitrary forms. Use "(| …)" for OR patterns, "PATTERN :as NAME" for AS patterns, and syntax like the usual Hy syntax for literal, capture, value, sequence, mapping, and class patterns. Guards are specified with ":if FORM". Here's a more complex example: (match #(100 200) [100 300] "Case 1" [100 200] :if flag "Case 2" [900 y] f"Case 3, y: {y}" [100 (| 100 200) :as y] f"Case 4, y: {y}" _ "Case 5, I match anything!") This will match case 2 if "flag" is true and case 4 otherwise. "match" can also match against class instances by keyword (or positionally if its "__match_args__" attribute is defined; see **PEP 636**): (import dataclasses [dataclass]) (defclass [dataclass] Point [] #^ int x #^ int y) (match (Point 1 2) (Point 1 x) :if (= (% x 2) 0) x) ; => 2 It's worth emphasizing that "match" is a pattern-matching construct rather than a generic switch construct, and retains all of Python's limitations on match patterns. For example, you can't match against the value of a variable. For more flexible branching constructs, see Hyrule's "branch" and "case", or simply use "cond". Exception-handling ------------------ macro(raise(exception :from other)) "raise" compiles to a "raise" statement, which throws an exception. With no arguments, the current exception is reraised. With one argument, an exception, that exception is raised. (try (raise KeyError) (except [KeyError] (print "gottem"))) "raise" supports one other syntax, "(raise EXCEPTION_1 :from EXCEPTION_2)", which compiles to "raise EXCEPTION_1 from EXCEPTION_2". macro(try(#* body)) "try" compiles to a "try" statement, which can catch exceptions and run cleanup actions. It begins with any number of body forms. Then follows any number of "except" or "except*" (**PEP 654**) forms, which are expressions that begin with the symbol in question, followed by a list of exception types, followed by more body forms. Finally there are an optional "else" form and an optional "finally" form, which again are expressions that begin with the symbol in question and then comprise body forms. Note that "except*" requires Python 3.11, and "except*" and "except" may not both be used in the same "try". Here's an example of several of the allowed kinds of child forms: (try (error-prone-function) (another-error-prone-function) (except [ZeroDivisionError] (print "Division by zero")) (except [[IndexError KeyboardInterrupt]] (print "Index error or Ctrl-C")) (except [e ValueError] (print "ValueError:" (repr e))) (except [e [TabError PermissionError ReferenceError]] (print "Some sort of error:" (repr e))) (else (print "No errors")) (finally (print "All done"))) Exception lists can be in any of several formats: * "[]" to catch any subtype of "Exception", like Python's "except:" * "[ETYPE]" to catch only the single type "ETYPE", like Python's "except ETYPE:" * "[[ETYPE1 ETYPE2 …]]" to catch any of the named types, like Python's "except ETYPE1, ETYPE2, …:" * "[VAR ETYPE]" to catch "ETYPE" and bind it to "VAR", like Python's "except ETYPE as VAR:" * "[VAR [ETYPE1 ETYPE2 …]]" to catch any of the named types and bind it to "VAR", like Python's "except ETYPE1, ETYPE2, … as VAR:" * "[[]]" or "[VAR []]" to catch no exceptions, like Python's "except ():". The return value of "try" is the last form evaluated among the main body, "except" forms, "except*" forms, and "else". Functions --------- macro(defn(name, #* args)) "defn" compiles to a *function definition* (or possibly to an assignment of a *lambda expression*). It always returns "None". It requires two arguments: a name (given as a symbol; see "fn" for anonymous functions) and a "lambda list", or list of parameters (also given as symbols). Any further arguments constitute the body of the function: (defn name [params] bodyform1 bodyform2…) An empty body is implicitly "(return None)". If there are at least two body forms, and the first of them is a string literal, this string becomes the docstring of the function. The final body form is implicitly returned; thus, "(defn f [] 5)" is equivalent to "(defn f [] (return 5))". There is one exception: due to Python limitations, no implicit return is added if the function is an asynchronous generator (i.e., defined with "(defn :async …)" or "(fn :async …)" and containing at least one "yield"). "defn" accepts a few more optional arguments: a literal keyword ":async" (to create a coroutine like Python's "async def"), a bracketed list of *decorators*, a list of type parameters (see below), and an annotation (see "annotate") for the return value. These are placed before the function name (in that order, if several are present): (defn :async [decorator1 decorator2] :tp [T1 T2] #^ annotation name [params] …) "defn" lambda lists support all the same features as Python parameter lists and hence are complex in their full generality. The simplest case is a (possibly empty) list of symbols, indicating that all parameters are required, and can be set by position, as in "(f value)", or by name, as in "(f :argument value)". To set a default value for a parameter, replace the parameter with the bracketed list "[pname value]", where "pname" is the parameter name as a symbol and "value" is an arbitrary form. Beware that, per Python, "value" is evaluated when the function is defined, not when it's called, and if the resulting object is mutated, all calls will see the changes. Further special lambda-list syntax includes: "/" If the symbol "/" is given in place of a parameter, it means that all the preceding parameters can only be set positionally. "*" If the symbol "*" is given in place of a parameter, it means that all the following parameters can only be set by name. "#* args" If the parameter list contains "#* args" or "(unpack-iterable args)", then "args" is set to a tuple containing all otherwise unmatched positional arguments. The name "args" is merely cherished Python tradition; you can use any symbol. "#** kwargs" "#** kwargs" (a.k.a. "(unpack-mapping kwargs)") is like "#* args", but collects unmatched keyword arguments into a dictionary. Each of these special constructs is allowed only once, and has the same restrictions as in Python; e.g., "#* args" must precede "#** kwargs" if both are present. Here's an example with a complex lambda list: (defn f [a / b [c 3] * d e #** kwargs] [a b c d e kwargs]) (print (hy.repr (f 1 2 :d 4 :e 5 :f 6))) ; => [1 2 3 4 5 {"f" 6}] Type parameters require Python 3.12, and have the semantics specified by **PEP 695**. The keyword ":tp" introduces the list of type parameters. Each item of the list is a symbol, an annotated symbol (such as "#^ int T"), or an unpacked symbol (such as "#* T" or "#** T"). As in Python, a single parameter can't be both annotated and unpacked. macro(fn(args)) As "defn", but no name for the new function is required (or allowed), and the newly created function object is returned. Decorators and type parameters aren't allowed, either. However, the function body is understood identically to that of "defn", without any of the restrictions of Python's "lambda". ":async" is also allowed. macro(return(object)) "return" compiles to a "return" statement. It exits the current function, returning its argument if provided with one, or "None" if not. (defn f [x] (for [n (range 10)] (when (> n x) (return n)))) (f 3.9) ; => 4 Note that in Hy, "return" is necessary much less often than in Python. The last form of a function is returned automatically, so an explicit "return" is only necessary to exit a function early. To get Python's behavior of returning "None" when execution reaches the end of a function, just put "None" there yourself: (defn f [] (setv d (dict :a 1 :b 2)) (.pop d "b") None) (print (f)) ; Prints "None", not "2" macro(yield(arg1, arg2)) "yield" compiles to a *yield expression*, which returns a value as a generator. For a plain yield, provide one argument, the value to yield, or omit it to yield "None". (defn naysayer [] (while True (yield "nope"))) (list (zip "abc" (naysayer))) ; => [#("a" "nope") #("b" "nope") #("c" "nope")] For a yield-from expression, provide two arguments, where the first is the literal keyword ":from" and the second is the subgenerator. (defn myrange [] (setv r (range 10)) (while True (yield :from r))) (list (zip "abc" (myrange))) ; => [#("a" 0) #("b" 1) #("c" 2)] macro(await(obj)) "await" creates an *await expression*. It takes exactly one argument: the object to wait for. (import asyncio) (defn :async main [] (print "hello") (await (asyncio.sleep 1)) (print "world")) (asyncio.run (main)) Macros ------ macro(defmacro(name, lambda-list, #* body)) Define a macro, at both compile-time and run-time. The syntax is a subset allowed of that by "defn": no decorator or return-type annotations are allowed, and the only types of parameter allowed are "symbol", "[symbol default-value]", "/", and "#* args". See Macros for details and examples. macro(hy.core.macros.defreader(_hy-compiler, key, #* body)) Define a reader macro, at both compile-time and run-time. After the name, all arguments are body forms: there is no parameter list as for "defmacro", since it's up to the reader macro to decide how to parse the source text following its call position. See Reader macros for details and examples. macro(hy.core.macros.get-macro(_hy-compiler, arg1, arg2)) Get the function object used to implement a macro. This works for all sorts of macros: core macros, global (i.e., module-level) macros, local macros, and reader macros. For regular (non-reader) macros, "get-macro" is called with one argument, a symbol or string literal, which can be premangled or not according to taste. For reader macros, this argument must be preceded by the literal keyword ":reader" (and note that the hash mark, "#", is not included in the name of the reader macro). (get-macro my-macro) (get-macro :reader my-reader-macro) Except when retrieving a local macro, "get-macro" expands to a "get" form on the appropriate object, such as "_hy_macros", selected at the time of expanding "get-macro". This means you can say "(del (get-macro …))", perhaps wrapped in "eval-and-compile" or "eval-when-compile", to delete a macro, but it's easy to get confused by the order of evaluation and number of evaluations. For more predictable results in complex situations, use "(del (get …))" directly instead of "(del (get-macro …))". macro(hy.core.macros.local-macros(_hy-compiler)) Expands to a dictionary mapping the mangled names of local macros to the function objects used to implement those macros. Thus, "local-macros" provides a rough local equivalent of "_hy_macros". (defn f [] (defmacro m [] "This is the docstring for the macro `m`." 1) (help (get (local-macros) "m"))) (f) The equivalency is rough in the sense that "local-macros" expands to a literal dictionary, not a preexisting object that Hy uses for resolving macro names. So, modifying the dictionary will have no effect. See also "get-macro". Classes ------- macro(defclass(arg1, #* args)) "defclass" compiles to a "class" statement, which creates a new class. It always returns "None". Only one argument, specifying the name of the new class as a symbol, is required. A list of *decorators* (and type parameters, in the same way as for "defn") may be provided before the class name. After the name comes a list of superclasses (use the empty list "[]" for the common case of no superclasses) and any number of body forms, the first of which may be a docstring. A simple class declaration and its uses might look like this: (defclass MyClass [] "A simple example class." (setv i 12345) (defn f [self] "hello world")) (setv instance (MyClass)) (print instance.i) ; => 12345 (print (.f instance)) ; => hello world A more complex declaration might look like this: (defclass [decorator1 decorator2] :tp [T1 T2] MyClass [SuperClass1 SuperClass2] "A class that does things at times." (setv attribute1 value1 attribute2 value2) (defn method1 [self arg1 arg2] …) (defn method2 [self arg1 arg2] …)) Modules ------- macro(import(#* forms)) "import" compiles to an "import" statement, which makes objects in a different module available in the current module. It always returns "None". Hy's syntax for the various kinds of import looks like this: ;; Import each of these modules. ;; Python: import sys, os.path (import sys os.path) ;; Import several names from a single module. ;; Python: from os.path import exists, isdir as is_dir, isfile (import os.path [exists isdir :as is-dir isfile]) ;; Import a module with an alias for the whole module. ;; Python: import sys as systest (import sys :as systest) ;; Import all objects from a module into the current namespace. ;; Python: from sys import * (import sys *) ;; You can list as many imports as you like of different types. ;; Python: ;; from tests.resources import kwtest, function_with_a_dash ;; from os.path import exists, isdir as is_dir, isfile as is_file ;; import sys as systest ;; from math import * (import tests.resources [kwtest function-with-a-dash] os.path [exists isdir :as is-dir isfile :as is-file] sys :as systest math *) "__all__" can be set to control what's imported by "(import module- name *)", as in Python, but beware that all names in "__all__" must be mangled. The macro "export" is a handy way to set "__all__" in a Hy program. macro(require(#* args)) "require" is a version of "import" for macros. It allows all the same syntax as "import", and brings the requested macros into the current scope at compile-time as well as run-time. The following are all equivalent ways to call a macro named "foo" in the module "mymodule": (require mymodule) (mymodule.foo 1) (require mymodule :as M) (M.foo 1) (require mymodule [foo]) (foo 1) (require mymodule *) (foo 1) (require mymodule [foo :as bar]) (bar 1) There's a bit of a trick involved in syntax such as "mymodule.foo". Namely, there is no object named "mymodule". Instead, "(require mymodule)" assigns every macro "foo" in "mymodule" to the name "(hy.mangle "mymodule.foo")" in "_hy_macros". Reader macros have a different namespace from regular macros, so they need to be specified with the added syntax ":readers […]". You could require a reader macro named "spiff" with the call "(require mymodule :readers [spiff])", or star-require reader macros with "(require mymodule :readers *)". For legibility, a regular-macros specification may analogously be prefixed ":macros": (require mymodule :macros [foo] :readers [spiff]) "require" with reader macros is more limited than with regular macros. You can't access reader macros with dotted names, and you can't rename them with ":as". Note that "(require mymodule :readers [spiff])" doesn't imply "(require mymodule)"; that is, "mymodule.foo" won't be made available. If you want that, use something like (require mymodule mymodule :readers [spiff]) To define which macros are collected by "(require mymodule *)", set the variable "_hy_export_macros" (analogous to Python's "__all__") to a list of mangled macro names, which is accomplished most conveniently with "export". The default behavior is analogous to "(import mymodule *)": all macros are collected other than those whose mangled names begin with an underscore ("_"), macro(hy.core.macros.export(#* args)) A convenience macro for defining "__all__" and "_hy_export_macros", which control which Python objects and macros (respectively) are collected by "*" imports in "import" and "require" (respectively). "export" allows you to provide the names as symbols instead of strings, and it calls "hy.mangle" for you on each name. The syntax is "(export objects macros)", where "objects" refers to Python objects and "macros" to macros. Keyword arguments are allowed. For example, (export :objects [my-fun MyClass] :macros [my-macro]) exports the function "my-fun", the class "MyClass", and the macro "my-macro". Miscellany ---------- macro(chainc(#* args)) "chainc" creates a *comparison expression*. It isn't required for unchained comparisons, which have only one comparison operator, nor for chains of the same operator. For those cases, you can use the comparison operators directly with Hy's usual prefix syntax, as in "(= x 1)" or "(< 1 2 3)". The use of "chainc" is to construct chains of heterogeneous operators, such as "x <= y < z". It uses an infix syntax with the general form (chainc ARG OP ARG OP ARG…) Hence, "(chainc x <= y < z)" is equivalent to "(and (<= x y) (< y z))", including short-circuiting, except that "y" is only evaluated once. Each "ARG" is an arbitrary form, which does not itself use infix syntax. Use "py" if you want fully Python-style operator syntax. You can also nest "chainc" forms, although this is rarely useful. Each "OP" is a literal comparison operator; other forms that resolve to a comparison operator are not allowed. At least two "ARG"s and one "OP" are required, and every "OP" must be followed by an "ARG". As elsewhere in Hy, the equality operator is spelled "=", not "==" as in Python. macro(assert(condition, [label None])) "assert" compiles to an "assert" statement, which checks whether a condition is true. The first argument, specifying the condition to check, is mandatory, whereas the second, which will be passed to "AssertionError", is optional. The whole form is only evaluated when "__debug__" is true, and the second argument is only evaluated when "__debug__" is true and the condition fails. "assert" always returns "None". (assert (= 1 2) "one should equal two") ; AssertionError: one should equal two Placeholder macros ------------------ There are a few core macros that are unusual in that all they do, when expanded, is crash, regardless of their arguments: * "else" * "except" * "except*" * "finally" * "unpack-mapping" * "unquote" * "unquote-splice" The purpose of these macros is merely to reserve their names. Each symbol is interpreted specially by one or more other core macros (e.g., "else" in "while") and thus, in these contexts, any definition of these names as a function or macro would be ignored. If you really want to, you can override these names like any others, but beware that, for example, trying to call your new "else" inside "while" may not work. Hy == A few core functions, mostly related to the manipulation of Hy code, are available through the module "hy". (hy.read(stream, filename, reader)) Like "hy.read-many", but only one form is read, and shebangs are forbidden. The model corresponding to this specific form is returned, or, if there are no forms left in the stream, "EOFError" is raised. "stream.pos" is left where it was immediately after the form. (hy.read-many(stream [filename ] reader [skip-shebang False])) Parse all the Hy source code in "stream", which should be a textual file-like object or a string. "filename", if provided, is used in error messages. If no "reader" is provided, a new "hy.HyReader" object is created. If "skip_shebang" is true and a shebang line is present, it's detected and discarded first. Return a value of type "hy.models.Lazy". If you want to evaluate this, be careful to allow evaluating each model before reading the next, as in "(hy.eval (hy.read-many o))". By contrast, forcing all the code to be read before evaluating any of it, as in "(hy.eval `(do [~@(hy.read-many o)]))", will yield the wrong result if one form defines a reader macro that's later used in the same stream to produce new forms. Warning: Thanks to reader macros, reading can execute arbitrary code. Don't read untrusted input. (hy.eval(model, globals, locals, module, macros)) An equivalent of Python's "eval()" for evaluating Hy code. The chief difference is that the first argument should be a model rather than source text. If you have a string of source text you want to evaluate, convert it to a model first with "hy.read" or "hy .read-many": (hy.eval '(+ 1 1)) ; => 2 (hy.eval (hy.read "(+ 1 1)")) ; => 2 The optional arguments "globals" and "locals" work as in the case of "eval()". Another optional argument, "module", can be a module object or a string naming a module. The module's "__dict__" attribute can fill in for "globals" (and hence also for "locals") if "module" is provided but "globals" isn't, but the primary purpose of "module" is to control where macro calls are looked up. Without this argument, the calling module of "hy.eval" is used instead. (defmacro my-test-mac [] 3) (hy.eval '(my-test-mac)) ; => 3 (import hyrule) (hy.eval '(my-test-mac) :module hyrule) ; NameError (hy.eval '(list-n 3 1) :module hyrule) ; => [1 1 1] Finally, finer control of macro lookup can be achieved by passing in a dictionary of macros as the "macros" argument. The keys of this dictionary should be mangled macro names, and the values should be function objects to implement those macros. This is the same structure as is produced by "local-macros", and in fact, "(hy.eval … :macros (local-macros))" is useful to make local macros visible to "hy.eval", which otherwise doesn't see them. (defn f [] (defmacro lmac [] 1) (hy.eval '(lmac)) ; NameError (print (hy.eval '(lmac) :macros (local-macros)))) ; => 1 (f) In any case, macros provided in this dictionary will shadow macros of the same name that are associated with the provided or implicit module. You can shadow a core macro, too, so be careful: there's no warning for this as there is in the case of "defmacro". (hy.repr(obj)) This function is Hy's equivalent of Python's "repr()". It returns a string representing the input object in Hy syntax. (hy.repr [1 2 3]) ; => "[1 2 3]" (repr [1 2 3]) ; => "[1, 2, 3]" Like "repr" in Python, "hy.repr" can round-trip many kinds of values. Round-tripping implies that given an object "x", "(hy.eval (hy.read (hy.repr x)))" returns "x", or at least a value that's equal to "x". A notable exception to round-tripping is that if a model contains a non-model, the latter will be promoted to a model in the output: (setv x (hy.models.List [5]) output (hy.repr x) y (hy.eval (hy.read output))) (print output) ; '[5] (print (type (get x 0))) ; (print (type (get y 0))) ; When "hy.repr" doesn't know how to represent an object, it falls back on "repr()". Use "hy.repr-register" to add your own conversion function for a type instead. (hy.repr-register(types, f, placeholder)) "hy.repr-register" lets you set the function that "hy.repr" calls to represent a type: (defclass C) (hy.repr-register C (fn [x] "cuddles")) (hy.repr [1 (C) 2]) ; => "[1 cuddles 2]" Registered functions often call "hy.repr" themselves. "hy.repr" will automatically detect self-references, even deeply nested ones, and output ""..."" for them instead of calling the usual registered function. To use a placeholder other than ""..."", pass a string of your choice as the "placeholder" argument: (defclass Container) (hy.repr-register Container :placeholder "HY THERE" (fn [x] f"(Container {(hy.repr x.value)})")) (setv container (Container)) (setv container.value container) (hy.repr container) ; => "(Container HY THERE)" (hy.mangle(s)) Stringify the argument (with "str", not "repr()" or "hy.repr") and convert it to a valid Python identifier according to Hy's mangling rules. (hy.mangle 'foo-bar) ; => "foo_bar" (hy.mangle "🦑") ; => "hyx_XsquidX" If the stringified argument is already both legal as a Python identifier and normalized according to Unicode normalization form KC (NFKC), it will be returned unchanged. Thus, "hy.mangle" is idempotent. (setv x '♦-->♠) (= (hy.mangle (hy.mangle x)) (hy.mangle x)) ; => True Generally, the stringifed input is expected to be parsable as a symbol. As a convenience, it can also have the syntax of a dotted identifier, and "hy.mangle" will mangle the dot-delimited parts separately. (hy.mangle "a.c!.d") ; => "a.hyx_cXexclamation_markX.d" (hy.unmangle(s)) Stringify the argument and try to convert it to a pretty unmangled form. See Hy's mangling rules. (hy.unmangle "hyx_XsquidX") ; => "🦑" Unmangling may not round-trip, because different Hy symbol names can mangle to the same Python identifier. In particular, Python itself already considers distinct strings that have the same normalized form (according to NFKC), such as "hello" and "𝔥𝔢𝔩𝔩𝔬", to be the same identifier. It's an error to call "hy.unmangle" on something that looks like a properly mangled name but isn't. For example, "(hy.unmangle "hyx_XpizzazzX")" is erroneous, because there is no Unicode character named "PIZZAZZ" (yet). (hy.macroexpand(model, module, macros)) As "hy.macroexpand-1", but the expansion process is repeated until it has no effect. (defmacro m [x] (and (int x) `(m ~(- x 1)))) (print (hy.repr (hy.macroexpand-1 '(m 5)))) ; => '(m 4) (print (hy.repr (hy.macroexpand '(m 5)))) ; => '0 Note that in general, macro calls in the arguments of the expression still won't expanded. To expand these, too, try Hyrule's "macroexpand-all". (hy.macroexpand-1(model, module, macros)) Check if "model" is an "Expression" specifying a macro call. If so, expand the macro and return the expansion; otherwise, return "model" unchanged. (defmacro m [x] `(do ~x ~x ~x)) (print (hy.repr (hy.macroexpand-1 '(m (+= n 1))))) ; => '(do (+= n 1) (+= n 1) (+= n 1)) An exceptional case is if the macro is a core macro that returns one of Hy's internal compiler result objects instead of a real model. Then, you just get the original back, as if the macro hadn't been expanded. As with "hy.eval", the optional arguments "module" and "macros" can be provided to control where macros are looked up, and local macros are invisible unless provided via e.g. ":macros (local-macros)". See also "hy.macroexpand". (hy.gensym([g ])) Generate a symbol with a unique name. The argument, if provided, will be included in the generated symbol name, as an aid to debugging. The below example uses the return value of "f" twice but calls it only once, and uses "hy.gensym" for the temporary variable to avoid collisions with any other variable names. (defmacro selfadd [x] (setv g (hy.gensym)) `(do (setv ~g ~x) (+ ~g ~g))) (defn f [] (print "This is only executed once.") 4) (print (selfadd (f))) (hy.as-model(x)) Convert "x" and any elements thereof into models recursively. This function is called implicitly by Hy in many situations, such as when inserting the expansion of a macro into the surrounding code, so you don't often need to call it. One use is to ensure that models are used on both sides of a comparison: (= 7 '7) ; => False (= (hy.as-model 7) '7) ; => True It's an error to call "hy.as-model" on an object that contains itself, or an object that isn't representable as a Hy literal, such as a function. class (hy.I) "hy.I" is an object that provides syntactic sugar for imports. It allows syntax like "(hy.I.math.sqrt 2)" to mean "(import math) (math.sqrt 2)", except without bringing "math" or "math.sqrt" into scope. (See hy.R for a version that requires a macro instead of importing a Python object.) This is useful in macros to avoid namespace pollution. To refer to a module with dots in its name, use slashes instead: "hy.I.os/path.basename" gets the function "basename" from the module "os.path". You can also call "hy.I" like a function, as in "(hy.I "math")", which is useful when the module name isn't known until run-time. This interface just calls "importlib.import_module()", avoiding (1) mangling due to attribute lookup, and (2) the translation of "/" to "." in the module name. The advantage of "(hy.I modname)" over "importlib.import_module(modname)" is merely that it avoids bringing "importlib" itself into scope. class (hy.R) There is no actual object named "hy.R". Rather, this syntax is recognized specially by the compiler as a shorthand for requiring and calling a macro. Readers ======= Hy's reader (i.e., parser) classes are most interesting to the user in the context of reader macros. class hy.HyReader(*, use_current_readers=False) A modular reader for Hy source. It inherits from "hy.Reader". When "use_current_readers" is true, initialize this reader with all reader macros from the calling module. fill_pos(model, start) Set position information for "model". "start" should be a (line number, column number) tuple for the start position, whereas the end position is set to the current cursor position. parse(stream, filename=None, skip_shebang=False) Yield all models in "stream". The parameters are understood as in "hy.read-many". parse_forms_until(closer) Yield models until the character "closer" is seen. This method is useful for reading sequential constructs such as lists. parse_one_form() Parse the next form in the stream and return its model. Any preceding whitespace and comments are skipped over. read_default(key) Try to read an identifier. If the next character after that is """, then instead parse it as a string with the given prefix (e.g., "r"...""). (This method is the default reader handler, for when nothing in the read table matches.) class hy.Reader An abstract base class for reading input character-by-character. See "hy.HyReader" for an example of creating a reader class. ends_ident The set of characters that indicate the end of an identifier Type: set[str] reader_table A dictionary mapping a reader-macro key to its dispatch function Type: dict[str, Callable] pos A read-only (line, column) tuple indicating the current cursor position of the source being read Type: tuple[int, int] chars(eof_ok=False) Consume and yield characters of the stream. If "eof_ok" is false (the default) and the end of the stream is reached, raise "hy.PrematureEndOfInput". dispatch(tag) Call the handler for the reader macro with key "tag" (a string). Return the model it produces, if any. end_identifier(character) A context manager to temporarily add a new character to the "ends_ident" set. getc() Consume one character from the stream and return it. This method does the bookkeeping for position data, so all character consumption should go through it. getn(n) Consume and return "n" characters. peek_and_getc(target) Peek at the next character and check if it's equal to "target", only consuming it if it's equal. A "bool" is returned. peekc() Peek at the next character, returning it but not consuming it. peeking(eof_ok=False) As "chars()", but without consuming any of the returned characters. This method is useful for looking several characters ahead. read_ident(just_peeking=False) Read characters until we hit something in "ends_ident". The characters are consumed unless "just_peeking" is true. saving_chars() A context manager to save all read characters. The value is a list of characters, rather than a single string. slurp_space() Consume and return zero or more whitespace characters. exception hy.PrematureEndOfInput(message, expression=None, filename=None, source=None, lineno=1, colno=1) Raised when input ends unexpectedly during parsing. Python operators ================ Python provides various *binary and unary operators*. These are usually invoked in Hy using core macros of the same name: for example, "(+ 1 2)" calls the core macro named "+", which uses Python's addition operator. There are a few exceptions to the names being the same: * "==" in Python is "=" in Hy. * "~" in Python is "bnot" in Hy. * "is not" in Python is "is-not" in Hy. * "not in" in Python is "not-in" in Hy. For Python's subscription expressions (like "x[2]"), Hy has two named macros, "get" and "cut". By importing from the module "hy.pyops" (typically with a star import, as in "(import hy.pyops *)"), you can also use these operators as functions. Functions are first-class objects, so you can say things like "(map - xs)" to negate all the numbers in the list "xs". Since macros shadow functions, forms like "(- 1 2)" will still call the macro instead of the function. The functions in "hy.pyops" have the same semantics as their macro equivalents, with one exception: functions can't short-circuit, so the functions for operators such as "and" and "!=" unconditionally evaluate all arguments. Hy also provides macros for *Python's augmented assignment operators* (but no equivalent functions, because Python semantics don't allow for this). These macros require at least two arguments even if the parent operator doesn't; for example, "(-= x)" is an error even though "(- x)" is legal. If the parent operator supports more than two arguments, though, so does the augmented-assignment version, using an aggregation operator to bind up all arguments past the first into a single rvalue. Typically, the aggregator is the same as the original operator: for example, "(+= count n1 n2 n3)" is equivalent to "(+= count (+ n1 n2 n3))". Exceptions (such as "-=", which uses the aggregator "+", so "(-= count n1 n2 n3)" is equivalent to "(-= count (+ n1 n2 n3))") are noted in the documentation for the parent operator (such as "-" for "-="). (hy.pyops.!=(a1, a2, #* a-rest)) The inequality operator. Its effect can be defined by the equivalent Python: * "(!= x y)" → "x != y" * "(!= a1 a2 … an)" → "a1 != a2 != … != an" (hy.pyops.%(x, y)) The modulus operator. Its effect can be defined by the equivalent Python: * "(% x y)" → "x % y" (hy.pyops.&(a1, #* a-rest)) The bitwise AND operator. Its effect can be defined by the equivalent Python: * "(& x)" → "x" * "(& x y)" → "x & y" * "(& a1 a2 … an)" → "a1 & a2 & … & an" (hy.pyops.*(#* args)) The multiplication operator. Its effect can be defined by the equivalent Python: * "(*)" → "1" * "(* x)" → "x" * "(* x y)" → "x * y" * "(* a1 a2 … an)" → "a1 * a2 * … * an" (hy.pyops.**(a1, a2, #* a-rest)) The exponentiation operator. Its effect can be defined by the equivalent Python: * "(** x y)" → "x ** y" * "(** a1 a2 … an)" → "a1 ** a2 ** … ** an" (hy.pyops.+(#* args)) The addition operator. Its effect can be defined by the equivalent Python: * "(+)" → "0" * "(+ x)" → "+x" * "(+ x y)" → "x + y" * "(+ a1 a2 … an)" → "a1 + a2 + … + an" (hy.pyops.-(a1, #* a-rest)) The subtraction operator. Its effect can be defined by the equivalent Python: * "(- x)" → "-x" * "(- x y)" → "x - y" * "(- a1 a2 … an)" → "a1 - a2 - … - an" Aggregator for augmented assignment: "+" (hy.pyops./(a1, #* a-rest)) The division operator. Its effect can be defined by the equivalent Python: * "(/ x)" → "1 / x" * "(/ x y)" → "x / y" * "(/ a1 a2 … an)" → "a1 / a2 / … / an" Aggregator for augmented assignment: "*" (hy.pyops.//(a1, a2, #* a-rest)) The floor division operator. Its effect can be defined by the equivalent Python: * "(// x y)" → "x // y" * "(// a1 a2 … an)" → "a1 // a2 // … // an" (hy.pyops.<(a1, #* a-rest)) The less-than operator. Its effect can be defined by the equivalent Python: * "(< x)" → "True" * "(< x y)" → "x < y" * "(< a1 a2 … an)" → "a1 < a2 < … < an" (hy.pyops.<<(a1, a2, #* a-rest)) The left shift operator. Its effect can be defined by the equivalent Python: * "(<< x y)" → "x << y" * "(<< a1 a2 … an)" → "a1 << a2 << … << an" Aggregator for augmented assignment: "+" (hy.pyops.<=(a1, #* a-rest)) The less-than-or-equal-to operator. Its effect can be defined by the equivalent Python: * "(<= x)" → "True" * "(<= x y)" → "x <= y" * "(<= a1 a2 … an)" → "a1 <= a2 <= … <= an" (hy.pyops.=(a1, #* a-rest)) The equality operator. Its effect can be defined by the equivalent Python: * "(= x)" → "True" * "(= x y)" → "x == y" * "(= a1 a2 … an)" → "a1 == a2 == … == an" (hy.pyops.>(a1, #* a-rest)) The greater-than operator. Its effect can be defined by the equivalent Python: * "(> x)" → "True" * "(> x y)" → "x > y" * "(> a1 a2 … an)" → "a1 > a2 > … > an" (hy.pyops.>=(a1, #* a-rest)) The greater-than-or-equal-to operator. Its effect can be defined by the equivalent Python: * "(>= x)" → "True" * "(>= x y)" → "x >= y" * "(>= a1 a2 … an)" → "a1 >= a2 >= … >= an" (hy.pyops.>>(a1, a2, #* a-rest)) The right shift operator. Its effect can be defined by the equivalent Python: * "(>> x y)" → "x >> y" * "(>> a1 a2 … an)" → "a1 >> a2 >> … >> an" Aggregator for augmented assignment: "+" (hy.pyops.@(a1, #* a-rest)) The matrix multiplication operator. Its effect can be defined by the equivalent Python: * "(@ x y)" → "x @ y" * "(@ a1 a2 … an)" → "a1 @ a2 @ … @ an" (hy.pyops.^(x, y)) The bitwise XOR operator. Its effect can be defined by the equivalent Python: * "(^ x y)" → "x ^ y" (hy.pyops.and(#* args)) The logical conjuction operator. Its effect can be defined by the equivalent Python: * "(and)" → "True" * "(and x)" → "x" * "(and x y)" → "x and y" * "(and a1 a2 … an)" → "a1 and a2 and … and an" (hy.pyops.bnot(x)) The bitwise NOT operator. Its effect can be defined by the equivalent Python: * "(bnot x)" → "~x" (hy.pyops.cut(coll, [arg1 sentinel], [arg2 sentinel], [arg3 sentinel])) "cut" compiles to a *slicing expression*, which selects multiple elements of a sequential data structure. The first argument is the object to be sliced. The remaining arguments are optional, and understood the same way as in a Python slicing expression. (setv x "abcdef") (cut x) ; => "abcdef" (cut x 2) ; => "ab" (cut x 2 None) ; => "cdef" (cut x 3 5) ; => "de" (cut x -3 None) ; => "def" (cut x 0 None 2) ; => "ace" A call to the "cut" macro (but not its function version in "hy.pyops") is a valid target for assignment (with "setv", "+=", etc.) and for deletion (with "del"). (hy.pyops.get(coll, key1, #* keys)) "get" compiles to one or more *subscription expressions*, which select an element of a data structure. The first two arguments are the collection object and a key; for example, "(get person name)" compiles to "person[name]". Subsequent arguments indicate chained subscripts, so "(get person name "surname" 0)" becomes "person[name]["surname"][0]". You can assign to a "get" form, as in (setv real-estate {"price" 1,500,000}) (setv (get real-estate "price") 0) but this doesn't work with the function version of "get" from "hy.pyops", due to Python limitations on lvalues. If you're looking for the Hy equivalent of Python list slicing, as in "foo[1:3]", note that this is just Python's syntactic sugar for "foo[slice(1, 3)]", and Hy provides its own syntactic sugar for this with a different macro, "cut". See also: * The dot macro ".", which can also subscript * Hyrule's "assoc", to easily assign multiple elements of a single collection (hy.pyops.in(a1, a2, #* a-rest)) The membership test operator. Its effect can be defined by the equivalent Python: * "(in x y)" → "x in y" * "(in a1 a2 … an)" → "a1 in a2 in … in an" (hy.pyops.is(a1, #* a-rest)) The identicality test operator. Its effect can be defined by the equivalent Python: * "(is x)" → "True" * "(is x y)" → "x is y" * "(is a1 a2 … an)" → "a1 is a2 is … is an" (hy.pyops.is-not(a1, a2, #* a-rest)) The negated identicality test operator. Its effect can be defined by the equivalent Python: * "(is-not x y)" → "x is not y" * "(is-not a1 a2 … an)" → "a1 is not a2 is not … is not an" (hy.pyops.not-in(a1, a2, #* a-rest)) The negated membership test operator. Its effect can be defined by the equivalent Python: * "(not-in x y)" → "x not in y" * "(not-in a1 a2 … an)" → "a1 not in a2 not in … not in an" (hy.pyops.or(#* args)) The logical disjunction operator. Its effect can be defined by the equivalent Python: * "(or)" → "None" * "(or x)" → "x" * "(or x y)" → "x or y" * "(or a1 a2 … an)" → "a1 or a2 or … or an" (hy.pyops.|(#* args)) The bitwise OR operator. Its effect can be defined by the equivalent Python: * "(|)" → "0" * "(| x)" → "x" * "(| x y)" → "x | y" * "(| a1 a2 … an)" → "a1 | a2 | … | an" Command-line interface ********************** Hy provides a handful of command-line programs for working with Hy code. Contents ^^^^^^^^ * hy * hy2py * hyc hy == "hy" is a command-line interface for Hy that in general imitates the program "python" provided by CPython. For example, "hy" without arguments launches the REPL if standard input is a TTY and runs the standard input as a script otherwise, whereas "hy foo.hy a b" runs the Hy program "foo.hy" with "a" and "b" as command-line arguments. See "hy --help" for a complete list of options and *Python's documentation* for many details. Here are some Hy-specific details: -m Much like Python's "-m", but the input module name will be mangled. --spy Print equivalent Python code before executing each piece of Hy code in the REPL: => (+ 1 2) 1 + 2 ------------------------------ 3 --repl-output-fn Set the REPL output function. This can be the name of a Python builtin, most likely "repr", or a dotted name like "foo.bar.baz". In the latter case, Hy will attempt to import the named object with code like "(import foo.bar [baz])". hy2py ===== "hy2py" is a program to convert Hy source code into Python source code. Use "hy2py --help" for usage instructions. It can take its input from standard input, or from a file or module name provided as a command-line argument. In the case of a module name, the current working directory should be the parent directory of that module, and the output parameter ("--output/-o") is required. When the output parameter is provided, the output will be written into the given folder or file. Otherwise, the result is written to standard output. Warning: "hy2py" can execute arbitrary code (via macros, "eval-when- compile", etc.). Don't give it untrusted input. Hy has no built-in capacity to translate Python to Hy, but see py2hy. hyc === "hyc" is a program to compile files of Hy code into Python bytecode. Use "hyc --help" for usage instructions. The generated bytecode files are named and placed according to the usual scheme of your Python executable, as indicated by "importlib.util.cache_from_source()". Warning: "hyc" can execute arbitrary code (via macros, "eval-when- compile", etc.). Don't give it untrusted input. Environment variables ********************* Hy treats the following environment variables specially. Boolean environment variables are interpreted as false when set to the empty string and true when set to anything else. HYSTARTUP (Default: nothing) Path to a file containing Hy source code to execute when starting the REPL. HY_SHOW_INTERNAL_ERRORS (Default: false) Whether to show some parts of tracebacks that point to internal Hy code and won't be helpful to the typical Hy user. HY_HISTORY (Default: "~/.hy-history") Path to which REPL input history will be saved. HY_MESSAGE_WHEN_COMPILING (Default: false) Whether to print "Compiling FILENAME" to standard error before compiling each file of Hy source code. This is helpful for debugging whether files are being loaded from bytecode or re- compiled. Developing Hy ************* Contents ^^^^^^^^ * Contributor guidelines * Issues * Pull requests * Deciding what to do * Commit formatting * Testing * Documentation * NEWS and AUTHORS * The PR itself * Contributor Code of Conduct * Core team Contributor guidelines ====================== Contributions are welcome and greatly appreciated. Every little bit helps in making Hy better. Potential contributions include: * Reporting and fixing bugs. * Requesting features. * Adding features. * Writing tests for outstanding bugs or untested features. * You can mark tests that Hy can't pass yet as xfail. * Cleaning up the code. * Improving the documentation. * Answering questions on the Github Discussions page or Stack Overflow. * Evangelizing for Hy in your organization, user group, conference, or bus stop. Issues ------ In order to report bugs or request features, search the issue tracker to check for a duplicate. (If you're reporting a bug, make sure you can reproduce it with the very latest, bleeding-edge version of Hy from the "master" branch on GitHub. Bugs in stable versions of Hy are fixed on "master" before the fix makes it into a new stable release.) If there aren't any duplicates, then you can make a new issue. It's totally acceptable to create an issue when you're unsure whether something is a bug or not. We'll help you figure it out. Use the same issue tracker to report problems with the documentation. Pull requests ------------- Submit proposed changes to the code or documentation as pull requests (PRs) on GitHub. Git can be intimidating and confusing to the uninitiated. This getting-started guide may be helpful. However, if you're overwhelmed by Git, GitHub, or the rules below, don't sweat it. We want to keep the barrier to contribution low, so we're happy to help you with these finicky things or do them for you if necessary. Deciding what to do ~~~~~~~~~~~~~~~~~~~ If you're proposing a major change to the Hy language, or you're unsure of the proposed change, create an issue to discuss it before you write any code. This will allow others to give feedback on your idea, and it can avoid wasted work. Commit formatting ~~~~~~~~~~~~~~~~~ Many PRs are small enough that only one commit is necessary, but bigger ones should be organized into logical units as separate commits. PRs should be free of merge commits and commits that fix or revert other commits in the same PR ("git rebase" is your friend). Avoid committing spurious whitespace changes. Don't commit comments tagged with things like "FIXME", "TODO", or "XXX". Ideas for how the code or documentation should change go in the issues list, not the code or documentation itself. The first line of a commit message should describe the overall change in 50 characters or less. If you wish to add more information, separate it from the first line with a blank line. Testing ~~~~~~~ Tests can be run by executing "pytest" in the root of this repository. New features and bug fixes should be tested. If you've caused an xfail test to start passing, remove the xfail mark. If you're testing a bug that has a GitHub issue, include a comment with the URL of the issue. No PR may be merged if it causes any tests to fail. The byte-compiled versions of the test files can be purged using "git clean -dfx tests/". If you want to run the tests while skipping the slow ones in "test_bin.py", use "pytest --ignore=tests/test_bin.py". Documentation ~~~~~~~~~~~~~ Generally, new features deserve coverage in the manual, either by editing the manual files directly or by changing docstrings that get included in the manual. To render the manual, install its dependencies with "pip install -r docs/requirements.txt" and then use the command "cd docs; sphinx-build . _build -b html". NEWS and AUTHORS ~~~~~~~~~~~~~~~~ If you're making user-visible changes to the code, add one or more items describing them to the NEWS file. Finally, add yourself to the AUTHORS file (as a separate commit): you deserve it. :) The PR itself ~~~~~~~~~~~~~ PRs should ask to merge a new branch that you created for the PR into hylang/hy's "master" branch, and they should have as their origin the most recent commit possible. If the PR fulfills one or more issues, then the body text of the PR (or the commit message for any of its commits) should say "Fixes #123" or "Closes #123" for each affected issue number. Use this exact (case- insensitive) wording, because when a PR containing such text is merged, GitHub automatically closes the mentioned issues, which is handy. Conversely, avoid this exact language if you want to mention an issue without closing it (because e.g. you've partly but not entirely fixed a bug). There are two situations in which a PR is allowed to be merged: 1. When it is approved by **two** members of Hy's core team other than the PR's author. Changes to the documentation, or trivial changes to code, need only **one** approving member. 2. When the PR is at least **three days** old and **no** member of the Hy core team has expressed disapproval of the PR in its current state. Anybody on the Hy core team may perform the merge. Merging should create a merge commit (don't squash unnecessarily, because that would remove separation between logically separate commits, and don't fast- forward, because that would throw away the history of the commits as a separate branch), which should include the PR number in the commit message. The typical workflow for this is to run the following commands on your own machine, then press the merge button on GitHub. $ git checkout master $ git pull $ git checkout $PR_BRANCH $ git fetch $ get reset --hard $REMOTE/$PR_BRANCH $ git rebase master $ git push -f Contributor Code of Conduct =========================== As contributors and maintainers of this project, we pledge to respect all people who contribute through reporting issues, posting feature requests, updating documentation, submitting pull requests or patches, and other activities. We are committed to making participation in this project a harassment- free experience for everyone, regardless of level of experience, gender, gender identity and expression, sexual orientation, disability, personal appearance, body size, race, ethnicity, age, or religion. Examples of unacceptable behavior by participants include the use of sexual language or imagery, derogatory comments or personal attacks, trolling, public or private harassment, insults, or other unprofessional conduct. Project maintainers have the right and responsibility to remove, edit, or reject comments, commits, code, wiki edits, issues, and other contributions that are not aligned to this Code of Conduct. Project maintainers who do not follow the Code of Conduct may be removed from the project team. This code of conduct applies both within project spaces and in public spaces when an individual is representing the project or its community. Instances of abusive, harassing, or otherwise unacceptable behavior may be reported by opening an issue or contacting one or more of the project maintainers. This Code of Conduct is adapted from the Contributor Covenant, version 1.1.0, available at http://contributor-covenant.org/version/1/1/0/. Core team ========= Hy's core development team consists of the following people: * Peter Andreev * Kodi B. Arfer * Allie Jo Casey * Sunjay Cauligi * Julien Danjou * Simon Gomizelj * Ryan Gonzalez * Morten Linderud * Matthew Odendahl * Paul Tagliamonte * Brandon T. Willard Python interoperability *********************** This chapter describes how to interact with Python code from Hy code and vice versa. Contents ^^^^^^^^ * Mangling * Keyword mincing * Libraries that expect Python * Packaging a Hy library * Using Python from Hy * Using Hy from Python Mangling ======== Mangling allows variable names to be spelled differently in Hy and Python. For example, Python's "str.format_map" can be written "str .format-map" in Hy, and a Hy function named "valid?" would be called "hyx_valid_Xquestion_markX" in Python. You can call "hy.mangle" and "hy.unmangle" from either language. Keyword mincing --------------- Another kind of mangling may be necessary in Python to refer to variables with the same name as reserved words. For example, while "(setv break 13)" is legal Hy, "import hy, my_hy_module; print(my_hy_module.break)" is syntactically invalid Python. String literals work, as in "getattr(my_hy_module, "break")", but to use what is syntactically a Python identifier, you'll have to take advantage of Python's Unicode normalization (via NFKC) and write something like "my_hy_module.𝐛reak". Here are all the MATHEMATICAL BOLD SMALL letters (U+1D41A through U+1D433) for convenient copying: 𝐚𝐛𝐜𝐝𝐞𝐟𝐠𝐡𝐢𝐣𝐤𝐥𝐦𝐧𝐨𝐩𝐪𝐫𝐬𝐭𝐮𝐯𝐰𝐱𝐲𝐳 Libraries that expect Python ============================ There are various means by which Hy may interact poorly with a Python library because the library doesn't account for the possibility of Hy. For example, when you run the program hy, "sys.executable" will be set to this program rather than the original Python binary. This is helpful more often than not, but will lead to trouble if e.g. the library tries to call "sys.executable" with the "-c" option. In this case, you can try setting "sys.executable" back to "hy.sys- executable", which is a saved copy of the original value. More generally, you can use hy2py, or you can put a simple Python wrapper script like "import hy, my_hy_program" in front of your code. See the wiki for tips on using specific packages. Packaging a Hy library ====================== Generally, the same infrastructure used for Python packages, such as "setup.py" files and the Python Package Index (PyPI), is applicable to Hy. Don't write the setup file itself in Hy, since you'll be declaring your package's dependence on Hy there, likely in the "install_requires" argument of "setup". Similarly, at the top level of the package, use "__init__.py" rather than "__init__.hy", and begin it with "import hy" to set up the import hooks for Hy. You can still import a Hy file from there in order to write the real logic in Hy. If you want allow users to import or require from the top level of your module, as in "from my_module import my_function" or "(require my- module [my-macro])", use an "__init__.py" such as import hy from my_module.hy_init import * hy.eval(hy.read('(require my-module.hy-init :macros * :readers *)')) If you want to compile your Hy code into Python bytecode at installation-time (in case e.g. the code is being installed to a directory where the bytecode can't be automatically written later, due to permissions issues), see Hy's own "setup.py" for an example. For PyPI packages, use the trove classifier "Programming Language :: Hy" for libraries meant to be useful for Hy specifically (e.g., a library that provides Hy macros) or other projects that are about Hy somehow (e.g., an instructive example Hy program). Don't use it for a package that just happens to be written in Hy. Using Python from Hy ==================== To use a Python module from Hy, just "import" it. In most cases, no additional ceremony is required. You can embed Python code directly into a Hy program with the macros "py" and "pys", and you can use standard Python tools like "eval()" or "exec()" to execute or manipulate Python code in strings. To translate Python code to Hy, see py2hy. Using Hy from Python ==================== To use a Hy module from Python, you can just "import" it, provided that "hy" has already been imported first, whether in the current module or in some earlier module executed by the current Python process. As mentioned previously, you can put "import hy" in a package's "__init__.py" to make this happen automatically. You can use hy2py to convert a Hy program to Python. The output will still import "hy", and thus require Hy to be installed in order to run; see Implicit names for details and workarounds. To execute Hy code from a string, use "hy.read-many" to convert it to models and "hy.eval" to evaluate it: >>> hy.eval(hy.read_many("(setv x 1) (+ x 1)")) 2 There is no Hy equivalent of "exec()" because "hy.eval" works even when the input isn't equivalent to a single Python expression. You can use "hy.REPL.run()" to launch the Hy REPL from Python, as in "hy.REPL(locals = {**globals(), **locals()}).run()". Macros ****** Macros, and the metaprogramming they enable, are one of the characteristic features of Lisp, and one of the main advantages Hy offers over vanilla Python. Much of the material covered in this chapter will be familiar to veterans of other Lisps, but there are also a lot of Hyly specific details. Contents ^^^^^^^^ * What are macros for? * Types of macros * Related constructs * When to use what * The basics * Pitfalls * Name games * Macro subroutines * The important take-home big fat WARNING * Reader macros * Macro namespaces and operations on macros What are macros for? ==================== The gist of metaprogramming is that it allows you to program the programming language itself (hence the word). You can create new control structures, like do-while, or other kinds of new syntax, like a concise literal notation for your favorite data structure. You can also modify how existing syntax is understood within a region of code, as by making identifiers that start with a capital letter implicitly imported from a certain module. Finally, metaprogramming can improve performance in some cases by effectively inlining functions, or by computing something once at compile-time rather than several times at run-time. With a Lisp-like macro system, you can metaprogram in a slicker and less error-prone way than generating code as text with conventional string formatting, or with lexer-level macros like those provided by the C preprocessor. Types of macros =============== Hy offers two types of macros: regular macros and reader macros. **Regular macros**, typically defined with "defmacro", are the kind Lispers usually mean when they talk about "macros". Regular macros are called like a function, with an expression whose head is the macro name: for example, "(foo a b)" could call a macro named "foo". A regular macro is called at compile-time, after the entire top-level form in which it appears is parsed, and receives parsed models as arguments. Regular macros come in three varieties, which vary in scope. **Reader macros**, typically defined with "defreader", are lower-level than regular macros. They're called with the hash sign "#"; for example, "#foo" calls a reader macro named "foo". A reader macro is called at parse-time. It doesn't receive conventional arguments. Instead, it uses an implicitly available parser object to parse the subsequent source text. When it returns, the standard Hy parser picks up where it left off. Related constructs ------------------ There are three other constructs that perform compile-time processing much like macros, and hence are worth mentioning here. * "do-mac" is essentially shorthand for defining and then immediately calling a regular macro with no arguments. * "eval-when-compile" evaluates some code at compile-time, but contributes no code to the final program, like a macro that returns "None" in a context where the "None" doesn't do anything. * "eval-and-compile" evaluates some code at compile-time, like "eval- when-compile", but also leaves the same code to be re-evaluated at run-time. When to use what ---------------- The variety of options can be intimidating. In addition to all of Hy's features listed above, Python is a dynamic programming language that allows you to do a lot of things at run-time that other languages would blanch at. For example, you can dynamically define a new class by calling "type". So, watch out for cases where your first thought is to use a macro, but you don't actually need one. When deciding what to use, a good rule of thumb is to use the least powerful option that suffices for the syntax, semantics, and performance that you want. So first, see if Python's dynamic features are enough. If they aren't, try a macro-like construct or a regular macro. If even those aren't enough, try a reader macro. Using the least powerful applicable option will help you avoid the macro pitfalls described below, as well as other headaches such as wanting to use a macro where a Python API needs a function. But for the sake of providing simpler examples, much of the below discussion will ignore this advice and consider example macros that could easily be written as functions. The basics ========== A regular macro can be defined with "defmacro" using a syntax similar to that of "defn". Here's how you could define and call a trivial macro that takes no arguments and returns a constant: (defmacro seventeen [] 17) (print (seventeen)) To see that "seventeen" is expanded at compile-time, run "hy2py" on this script and notice that it ends with "print(17)" rather than "print(seventeen())". If you insert a "print" call inside the macro definition, you'll also see that the print happens when the file is compiled, but not when it's rerun (so long as an up-to-date bytecode file exists). A more useful macro returns code. You can construct a model the long way, like this: (defmacro addition [] (hy.models.Expression [ (hy.models.Symbol "+") (hy.models.Integer 1) (hy.models.Integer 1)])) or more concisely with "quote", like this: (defmacro addition [] '(+ 1 1)) You don't need to always return a model because the compiler calls "hy .as-model" on everything before trying to compile it. Thus, the "17" above works fine in place of "(hy.models.Integer 17)". But trying to compile something that "hy.as-model" chokes on, like a function object, is an error. Arguments are always passed in as models. You can use quasiquotation (see "quasiquote") to concisely define a model with partly literal and partly evaluated components: (defmacro set-to-2 [variable] `(setv ~variable 2)) (set-to-2 foobar) (print foobar) Macros don't understand keyword arguments like functions do. Rather, the keyword objects themselves are passed in literally. This gives you flexibility in how to handle them. Thus, "#** kwargs" and "*" aren't allowed in the parameter list of a macro, although "#* args" and "/" are. See "hyrule.defmacro-kwargs" if you want to handle keyword arguments like a function. On the inside, macros are functions, and obey the usual Python semantics for functions. For example, "setv" inside a macro will define or modify a variable local to the current macro call, and "return" ends macro execution and uses its argument as the expansion. Macros from other modules can be brought into the current scope with "require". Pitfalls ======== Macros are powerful, but with great power comes great potential for anguish. There are a few characteristic issues you need to guard against to write macros well, and, to a lesser extent, even to use macros well. Name games ---------- A lot of these issues are variations on the theme of names not referring to what you intend them to, or in other words, surprise shadowing. For example, the macro below was intended to define a new variable named "x", but it ends up modifying a preexisting variable. (defmacro upper-twice [arg] `(do (setv x (.upper ~arg)) (+ x x))) (setv x "Okay guys, ") (setv salutation (upper-twice "bye")) (print (+ x salutation)) ; Intended result: "Okay guys, BYEBYE" ; Actual result: "BYEBYEBYE" If you avoid the assignment entirely, by using an argument more than once, you can cause a different problem: surprise multiple evaluation. (defmacro upper-twice [arg] `(+ (.upper ~arg) (.upper ~arg))) (setv items ["a" "b" "c"]) (print (upper-twice (.pop items))) ; Intended result: "CC" ; Actual result: "CB" A better approach is to use "hy.gensym" to choose your variable name: (defmacro upper-twice [arg] (setv g (hy.gensym)) `(do (setv ~g (.upper ~arg)) (+ ~g ~g))) Hyrule provides some macros that make using gensyms more convenient, like "defmacro!" and "def-gensyms". On the other hand, you can write a macro that advertises a specific name (or set of names) as part of its interface. For example, Hyrule's anaphoric macro "ap-if" assigns the result of a test form to "it", and allows the caller to include forms that refer to "it": (import os) (ap-if (.get os.environ "PYTHONPATH") (print "Your PYTHONPATH is" it)) Macro subroutines ----------------- A case where you could want something to be in the scope of a macro's expansion, and then it turns out not to be, is when you want to call a function or another macro in the expansion: (defmacro hypotenuse [a b] (import math) `(math.sqrt (+ (** ~a 2) (** ~b 2)))) (print (hypotenuse 3 4)) ; NameError: name 'math' is not defined The form "(import math)" here appears in the wrong context, in the macro call itself rather than the expansion. You could use "import" or "require" to bind the module name or one of its members to a gensym, but an often more convenient option is to use the one-shot import syntax "hy.I" or the one-shot require syntax hy.R: (defmacro hypotenuse [a b] `(hy.I.math.sqrt (+ (** ~a 2) (** ~b 2)))) (print (hypotenuse 3 4)) A related but distinct issue is when you want to use a function (or other ordinary Python object) in a macro's code, but it isn't available soon enough: (defn subroutine [x] (hy.models.Symbol (.upper x))) (defmacro uppercase-symbol [x] (subroutine x)) (setv (uppercase-symbol foo) 1) ; NameError: name 'subroutine' is not defined Here, "subroutine" is only defined at run-time, so "uppercase-symbol" can't see it when it's expanding (unless you happen to be calling "uppercase-symbol" from a different module). This is easily worked around by wrapping "(defn subroutine …)" in "eval-and-compile" (or "eval-when-compile" if you want "subroutine" to be invisible at run- time). By the way, despite the need for "eval-and-compile", extracting a lot of complex logic out of a macro into a function is often a good idea. Functions are typically easier to debug and to make use of in other macros. The important take-home big fat WARNING --------------------------------------- A typical macro should use only names of these four kinds in its expansion: * gensyms * core macros * objects that Python puts in scope by default (like its built-in functions) * "hy" and its attributes It's possible to rebind nearly all these names, so surprise shadowing is still theoretically possible. Unfortunately, the only way to prevent these pathological rebindings from coming about is… don't do that. Don't make a new macro named "setv" or name a function parameter "type" unless you're ready for every macro you call to break, the same way you wouldn't monkey-patch a built-in Python module without thinking carefully. This kind of thing is the responsibility of the macro caller; the macro writer can't do much to defend against it. There is at least a pragma warn-on-core-shadow, enabled by default, that causes "defmacro" and "require" to warn you if you give your new macro the same name as a core macro. Reader macros ============= Reader macros allow you to hook into Hy's parser to customize how text is parsed into models. They're defined with "defreader", or, like regular macros, brought in from other modules with "require". Rather than receiving function arguments, a reader macro has access to a "hy.HyReader" object named "&reader", which provides all the text- parsing logic that Hy uses to parse itself (see "hy.HyReader" and its base class "hy.Reader" for the available methods). A reader macro is called with the hash sign "#", and like a regular macro, it should return a model or something convertible to a model. The simplest kind of reader macro doesn't read anything: (defreader hi '(print "Hello.")) #hi #hi #hi A less trivial, and more common, usage of reader macros is to call "hy.HyReader.parse_one_form()" to get a single form from the following source text. Such a reader macro is like a unary regular macro that's called with "#" instead of parentheses. (defreader do-twice (setv x (.parse-one-form &reader)) `(do ~x ~x)) #do-twice (print "This line prints twice.") Here's a moderately complex example of a reader macro that couldn't be implemented as a regular macro. It reads in a list of lists in which the inner lists are newline-separated, but newlines are allowed inside elements. (defreader matrix (.slurp-space &reader) (setv start (.getc &reader)) (assert (= start "[")) (.slurp-space &reader) (setv out [[]]) (while (not (.peek-and-getc &reader "]")) (cond (any (gfor c " \t" (.peek-and-getc &reader c))) None (.peek-and-getc &reader "\n") (.append out []) True (.append (get out -1) (.parse-one-form &reader)))) (lfor line out :if line line)) (print (hy.repr #matrix [ 1 (+ 1 1) 3 4 ["element" "containing" "a" "newline"] 6 7 8 9])) ; => [[1 2 3] [4 ["element" "containing" "a" "newline"] 6] [7 8 9]] Note that because reader macros are evaluated at parse-time, and top- level forms are completely parsed before any further compile-time execution occurs, you can't use a reader macro in the same top-level form that defines it: (do (defreader up (.slurp-space &reader) (.upper (.read-one-form &reader))) (print #up "hello?")) ; LexException: reader macro '#up' is not defined Of the potential problems discussed above that apply to regular macros, such as surprise shadowing, most also apply to reader macros. Macro namespaces and operations on macros ========================================= Macros don't share namespaces with ordinary Python objects. That's why something like "(defmacro m []) (print m)" fails with a "NameError", and how "hy.pyops" can provide a function named "+" without hiding the core macro "+". There are three scoped varieties of regular macro. First are **core macros**, which are built into Hy; the set of core macros is fixed. They're available by default. You can inspect them in the dictionary "bulitins._hy_macros", which is attached to Python's usual "builtins" module. The keys are strings giving mangled names and the values are the function objects implementing the macros. **Global macros** are associated with modules, like Python global variables. They're defined when you call "defmacro" or "require" in a global scope. You can see them in the global variable "_hy_macros" associated with the same module. You can manipulate "_hy_macros" to list, add, delete, or get help on macros, but be sure to use "eval- and-compile" or "eval-when-compile" when you need the effect to happen at compile-time, which is often. (Modifying "bulitins._hy_macros" is of course a risky proposition.) Here's an example, which also demonstrates the core macro "get-macro". "get-macro" provides syntactic sugar for getting all sorts of macros as objects. (defmacro m [] "This is a docstring." '(print "Hello, world.")) (print (in "m" _hy_macros)) ; => True (help (get-macro m)) (m) ; => "Hello, world." (eval-and-compile (del (get _hy_macros "m"))) (m) ; => NameError (eval-and-compile (setv (get _hy_macros (hy.mangle "new-mac")) (fn [] '(print "Goodbye, world.")))) (new-mac) ; => "Goodbye, world." **Local macros** are associated with function, class, or comprehension scopes, like Python local variables. They come about when you call "defmacro" or "require" in an appropriate scope. You can call "local- macros" to view local macros, but adding or deleting elements is ineffective. Beware that local macro definitions apply to the results of expanding other macros in the given context, and hence may not be as local as you expect: (defmacro number [] 1) (defmacro uses-number [] '(number)) (defn f [] (defmacro number [] 2) (uses-number)) (print (uses-number)) ; => 1 (print (f)) ; => 2 (print (uses-number)) ; => 1 For this reason, shadowing a core macro is risky even with a local macro. Finally, "_hy_reader_macros" is a per-module dictionary like "_hy_macros" for reader macros, but here, the keys aren't mangled. There are no local reader macros, and there's no official way to introspect on Hy's handful of core reader macros. So, of the three scoped varieties of regular macro, reader macros most resemble global macros. Model patterns ************** The module "hy.model-patterns" provides a library of parser combinators for parsing complex trees of Hy models. Model patterns exist mostly to help implement the compiler, but they can also be useful for writing macros. A motivating example ==================== The kind of problem that model patterns are suited for is the following. Suppose you want to validate and extract the components of a form like: (setv form '(try (foo1) (foo2) (except [EType1] (foo3)) (except [e EType2] (foo4) (foo5)) (except [] (foo6)) (finally (foo7) (foo8)))) You could do this with loops and indexing, but it would take a lot of code and be error-prone. Model patterns concisely express the general form of a model tree to be matched, like what a regular expression does for text. Here's a pattern for a "try" form of the above kind: (import funcparserlib.parser [maybe many] hy.model-patterns *) (setv parser (whole [ (sym "try") (many (notpexpr "except" "else" "finally")) (many (pexpr (sym "except") (| (brackets) (brackets FORM) (brackets SYM FORM)) (many FORM))) (maybe (dolike "else")) (maybe (dolike "finally"))])) You can run the parser with "(.parse parser form)". The result is: #( ['(foo1) '(foo2)] [ '([EType1] [(foo3)]) '([e EType2] [(foo4) (foo5)]) '([] [(foo6)])] None '((foo7) (foo8))) which is conveniently utilized with an assignment such as "(setv [body except-clauses else-part finally-part] result)". Notice that "else- part" will be set to "None" because there is no "else" clause in the original form. Usage ===== Model patterns are implemented as funcparserlib parser combinators. We won't reproduce funcparserlib's own documentation, but here are some important built-in parsers: * "(+ ...)" matches its arguments in sequence. * "(| ...)" matches any one of its arguments. * "(>> parser function)" matches "parser", then feeds the result through "function" to change the value that's produced on a successful parse. * "(skip parser)" matches "parser", but doesn't add it to the produced value. * "(maybe parser)" matches "parser" if possible. Otherwise, it produces the value "None". * "(some function)" takes a predicate "function" and matches a form if it satisfies the predicate. Some of the more important of Hy's own parsers are: * "FORM" matches anything. * "SYM" matches any symbol. * "sym" matches and discards (per "skip") the named symbol or keyword. * "brackets" matches the arguments in square brackets. * "pexpr" matches the arguments in parentheses. Here's how you could write a simple macro using model patterns: (defmacro pairs [#* args] (import funcparserlib.parser [many] hy.model-patterns [whole SYM FORM]) (setv [args] (.parse (whole [(many (+ SYM FORM))]) args)) `[~@(gfor [a1 a2] args #((str a1) a2))]) (print (hy.repr (pairs a 1 b 2 c 3))) ; => [#("a" 1) #("b" 2) #("c" 3)] A failed parse will raise "funcparserlib.parser.NoParseError". Reference ========= Parser combinators for pattern-matching Hy model trees. hy.model_patterns.FORM = Match any token. hy.model_patterns.KEYWORD = Match a "Keyword". hy.model_patterns.LITERAL = Match any model type denoting a literal. hy.model_patterns.STR = Match a "String". hy.model_patterns.SYM = Match a "Symbol". class hy.model_patterns.Tag(tag, value) A named tuple; see "collections.namedtuple()" and "tag()". tag Alias for field number 0 value Alias for field number 1 hy.model_patterns.braces(*parsers, name=None) Match the given parsers inside curly braces (a "Dict"). hy.model_patterns.brackets(*parsers, name=None) Match the given parsers inside square brackets (a "List"). hy.model_patterns.dolike(head) Parse a "do"-like expression. "head" is a string used to construct a symbol for the head. hy.model_patterns.in_tuple(*parsers, name=None) Match the given parsers inside a "Tuple". hy.model_patterns.keepsym(wanted) As "sym()", but the object is kept instead of skipped. hy.model_patterns.notpexpr(*disallowed_heads) Parse any object other than an expression headed by a symbol whose name is equal to one of the given strings. hy.model_patterns.parse_if(pred, parser) Return a parser that parses a token with "parser" if it satisfies the predicate "pred". hy.model_patterns.pexpr(*parsers, name=None) Match the given parsers inside a parenthesized "Expression". hy.model_patterns.sym(wanted) Match and skip a symbol with a name equal to the string "wanted". You can begin the string with "":"" to check for a keyword instead. hy.model_patterns.tag(tag_name, parser) Match on "parser" and produce an instance of "Tag" with "tag" set to "tag_name" and "value" set to result of matching "parser". hy.model_patterns.times(lo, hi, parser) Parse "parser" several times (from "lo" to "hi", inclusive) in a row. "hi" can be "float('inf')". The result is a list no matter the number of instances. hy.model_patterns.unpack(kind, content_type=None) Parse an unpacking form, returning it unchanged. "kind" should be ""iterable"", ""mapping"", or ""either"". If "content_type" is provided, the parser also checks that the unpacking form has exactly one argument and that argument inherits from "content_type". hy.model_patterns.whole(parsers) Match the parsers in the given list one after another, then expect the end of the input. The Hy REPL *********** Hy's read-eval-print loop (REPL) is implemented in the class "hy.REPL". The REPL can be started interactively from the command line or programmatically with the instance method "hy.REPL.run()". Two environment variables useful for the REPL are "HY_HISTORY", which specifies where the REPL input history is saved, and "HYSTARTUP", which specifies a file to run when the REPL starts. Due to Python limitations, a Python "code.InteractiveConsole" launched inside the Hy REPL, or a Hy REPL inside another Hy REPL, may malfunction. class hy.REPL(spy=False, spy_delimiter='------------------------------', output_fn=None, locals=None, filename='', allow_incomplete=True) A subclass of "code.InteractiveConsole" for Hy. A convenient way to use this class to interactively debug code is to insert the following in the code you want to debug: (.run (hy.REPL :locals {#** (globals) #** (locals)})) Or in Python: import hy; hy.REPL(locals = {**globals(), **locals()}).run() Note that as with "code.interact()", changes to local variables inside the REPL are not propagated back to the original scope. run() Start running the REPL. Return 0 when done. Output functions ================ By default, the return value of each REPL input is printed with "hy.repr". To change this, you can set the REPL output function with e.g. the command-line argument "--repl-output-fn". Use "repr()" to get Python representations, like Python's own REPL. Regardless of the output function, no output is produced when the value is "None", as in Python. Special variables ================= The REPL maintains a few special convenience variables. "*1" holds the result of the most recent input, like "_" in the Python REPL. "*2" holds the result of the input before that, and "*3" holds the result of the input before that. Finally, "*e" holds the most recent uncaught exception. Startup files ============= Any macros or Python objects defined in the REPL startup file will be brought into the REPL's namespace. A few variables are special in the startup file: "repl-spy" If true, print equivalent Python code before executing each piece of Hy code. "repl-output-fn" The output function, as a unary callable object. "repl-ps1", "repl-ps2" Strings to use as the prompt strings "sys.ps1" and "sys.ps2" for the Hy REPL. Hy startup files can do a number of other things like set banner messages or change the prompts. The following example shows a number of possibilities: ;; Wrapping in an `eval-and-compile` ensures these Python packages ;; are available in macros defined in this file as well. (eval-and-compile (import sys os) (sys.path.append "~/")) (import re json pathlib [Path] hy.pyops * hyrule [pp pformat]) (require hyrule [unless]) (setv repl-spy True repl-output-fn pformat ;; Make the REPL prompt `=>` green. repl-ps1 "\x01\x1b[0;32m\x02=> \x01\x1b[0m\x02" ;; Make the REPL prompt `...` red. repl-ps2 "\x01\x1b[0;31m\x02... \x01\x1b[0m\x02") (defn slurp [path] (setv path (Path path)) (when (path.exists) (path.read-text))) (defmacro greet [person] `(print ~person)) Semantics ********* This chapter describes features of Hy semantics that differ from Python's and aren't better categorized elsewhere, such as in the chapter Macros. Each is a potential trap for the unwary. Contents ^^^^^^^^ * Implicit names * Order of evaluation * When bytecode is regenerated * Traceback positioning Implicit names ============== Every compilation unit (basically, module) implicitly begins with "(import hy)". You can see it in the output of "hy2py". The purpose of this is to ensure Hy can retrieve any names it needs to compile your code. For example, the code "(print '(+ 1 1))" requires constructing a "hy.models.Expression". Thus you should be wary of assigning to the name "hy", even locally, because then the wrong thing can happen if the generated code tries to access "hy" expecting to get the module. As a bonus, you can say things like "(print (hy.repr #(1 2)))" without explicitly importing "hy" first. If you restrict yourself to a subset of Hy, it's possible to write a Hy program, translate it to Python with "hy2py", remove the "import hy", and get a working Python program that doesn't depend on Hy itself. Unfortunately, Python is too dynamic for the Hy compiler to be able to tell in advance when this will work, which is why the automatic import is unconditional. Hy needs to create temporary variables to accomplish some of its tricks. For example, in order to represent "(print (with …))" in Python, the result of the "with" form needs to be set to a temporary variable. These names begin with "_hy_", so it's wise to avoid this prefix in your own variable names. Such temporary variables are scoped in the same way surrounding ordinary variables are, and they aren't explicitly cleaned up, so theoretically, they can waste memory and lead to "object.__del__()" being called later than you expect. When in doubt, check the "hy2py" output. Order of evaluation =================== Like many programming languages, but unlike Python, Hy doesn't guarantee in all cases the order in which function arguments are evaluated. More generally, the evaluation order of the child models of a "hy.models.Sequence" is unspecified. For example, "(f (g) (h))" might evaluate (part of) "(h)" before "(g)", particularly if "f" is a function whereas "h" is a macro that produces Python-level statements. So if you need to be sure that "g" is called first, call it before "f". When bytecode is regenerated ============================ The first time Hy is asked to execute a file, whether directly or indirectly (as in the case of an import), it will produce a bytecode file (unless "PYTHONDONTWRITEBYTECODE" is set). Subsequently, if the source file hasn't changed, Hy will load the bytecode instead of recompiling the source. Python also makes bytecode files, but the difference between recompilation and loading bytecode is more consequential in Hy because of how Hy lets you run and generate code at compile-time with things like macros, reader macros, and "eval-and- compile". You may be surprised by behavior like the following: $ echo '(defmacro m [] 1)' >a.hy $ echo '(require a) (print (a.m))' >b.hy $ hy b.hy 1 $ echo '(defmacro m [] 2)' >a.hy $ hy b.hy 1 Why didn't the second run of "b.hy" print "2"? Because "b.hy" was unchanged, so it didn't get recompiled, so its bytecode still had the old expansion of the macro "m". Traceback positioning ===================== When an exception results in a traceback, Python uses line and column numbers associated with AST nodes to point to the source code associated with the exception: Traceback (most recent call last): File "cinco.py", line 4, in find() File "cinco.py", line 2, in find print(chippy) ^^^^^^ NameError: name 'chippy' is not defined This position information is stored as attributes of the AST nodes. Hy tries to set these attributes appropriately so that it can also produce correctly targeted tracebacks, but there are cases where it can't, such as when evaluating code that was built at runtime out of explicit calls to model constructors. Python still requires line and column numbers, so Hy sets these to 1 as a fallback; consequently, tracebacks can point to the beginning of a file even though the relevant code isn't there. Syntax ****** This chapter describes how Hy source code is understood at the level of text, as well as the abstract syntax objects that the reader (a.k.a. the parser) turns text into, as when invoked with "hy.read". The basic units of syntax at the textual level are called **forms**, and the basic objects representing forms are called **models**. Following Python, Hy is in general case-sensitive. For example, "foo" and "FOO" are different symbols, and the Python-level variables they refer to are also different. Contents ^^^^^^^^ * An introduction to models * Non-form syntactic elements * Shebang * Whitespace * Comments * Discard prefix * Identifiers * Numeric literals * Dotted identifiers * Symbols * Mangling * Keywords * String literals * Bracket strings * Sequential forms * Expressions * List, tuple, and set literals * Dictionary literals * Format strings * Additional sugar * Reader macros An introduction to models ========================= Reading a Hy program produces a nested structure of model objects. Models can be very similar to the kind of value they represent (such as "Integer", which is a subclass of "int") or they can be somewhat different (such as "Set", which is ordered, unlike actual "set"s). All models inherit from "Object", which stores textual position information, so tracebacks can point to the right place in the code. The compiler takes whatever models are left over after parsing and macro-expansion and translates them into Python "ast" nodes (e.g., "Integer" becomes "ast.Constant"), which can then be evaluated or rendered as Python code. Macros (that is, regular macros, as opposed to reader macros) operate on the model level, taking some models as arguments and returning more models for compilation or further macro- expansion; they're free to do quite different things with a given model than the compiler does, if it pleases them to, like using an "Integer" to construct a "Symbol". In general, a model doesn't count as equal to the value it represents. For example, "(= (hy.models.String "foo") "foo")" returns "False". But you can promote a value to its corresponding model with "hy.as-model", or you can demote a model with the usual Python constructors like "str" or "int", or you can evaluate a model as Hy code with "hy.eval". Models can be created with the constructors, with the "quote" or "quasiquote" macros, or with "hy.as-model". Explicit creation is often not necessary, because the compiler will automatically promote (via "hy.as-model") any object it's trying to evaluate. Note that when you want plain old data structures and don't intend to produce runnable Hy source code, you'll usually be better off using Python's basic data structures ("tuple", "list", "dict", etc.) than models. Yes, "homoiconicity" is a fun word, but a Hy "List" won't provide any advantage over a Python "list" when you're managing a list of email addresses or something. The default representation of models (via "hy.repr") uses quoting for readability, so "(hy.models.Integer 5)" is represented as "'5". Python representations (via "repr()") use the constructors, and by default are pretty-printed; you can disable this globally by setting "hy.models.PRETTY" to "False", or temporarily with the context manager "hy.models.pretty". class hy.models.Object An abstract base class for Hy models, which represent forms. class hy.models.Lazy(gen) The output of "hy.read-many". It represents a sequence of forms, and can be treated as an iterator. Reading each form lazily, only after evaluating the previous form, is necessary to handle reader macros correctly; see "hy.read-many". Non-form syntactic elements =========================== Shebang ------- If a Hy program begins with "#!", Hy assumes the first line is a shebang line and ignores it. It's up to your OS to do something more interesting with it. Shebangs aren't real Hy syntax, so "hy.read-many" only allows them if its option "skip_shebang" is enabled. Whitespace ---------- Hy has lax whitespace rules less similar to Python's than to those of most other programming languages. Whitespace can separate forms (e.g., "a b" is two forms whereas "ab" is one) and it can occur inside some forms (like string literals), but it's otherwise ignored by the reader, producing no models. The reader only grants this special treatment to the ASCII whitespace characters, namely U+0009 (horizontal tab), U+000A (line feed), U+000B (vertical tab), U+000C (form feed), U+000D (carriage return), and U+0020 (space). Non-ASCII whitespace characters, such as U+2009 (THIN SPACE), are treated as any other character. So yes, you can have exotic whitespace characters in variable names, although this is only especially useful for obfuscated code contests. Comments -------- Comments begin with a semicolon (";") and continue through the end of the line. There are no multi-line comments in the style of C's "/* … */", but you can use the discard prefix or string literals for similar purposes. Discard prefix -------------- Like Clojure, Hy supports the Extensible Data Notation discard prefix "#_", which is kind of like a structure-aware comment. When the reader encounters "#_", it reads and then discards the following form. Thus "#_" is like ";" except that reader macros still get executed, and normal parsing resumes after the next form ends rather than at the start of the next line: "[dilly #_ and krunk]" is equivalent to "[dilly krunk]", whereas "[dilly ; and krunk]" is equivalent to just "[dilly". Comments indicated by ";" can be nested within forms discarded by "#_", but "#_" has no special meaning within a comment indicated by ";". Identifiers =========== Identifiers are a broad class of syntax in Hy, comprising not only variable names, but any nonempty sequence of characters that aren't ASCII whitespace nor one of the following: "()[]{};"'`~". Identifiers also aren't recognized if they parse as something else, like a keyword. The reader will attempt to read an identifier as each of the following types, in the given order: 1. a numeric literal 2. a dotted identifier 3. a symbol Numeric literals ---------------- All of *Python's syntax for numeric literals* is supported in Hy, resulting in an "Integer", "Float", or "Complex". Hy also provides a few extensions: * Commas (",") can be used like underscores ("_") to separate digits without changing the result. Thus, "10_000_000_000" may also be written "10,000,000,000". Hy is also more permissive about the placement of separators than Python: several may be in a row, and they may be after all digits, after ".", "e", or "j", or even inside a radix prefix. Separators before the first digit are still forbidden because e.g. "_1" is a legal Python variable name, so it's a symbol in Hy rather than an integer. * Integers can begin with leading zeroes, even without a radix prefix like "0x". Leading zeroes don't automatically cause the literal to be interpreted in octal like they do in C. For octal, use the prefix "0o", as in Python. * "NaN", "Inf", and "-Inf" are understood as literals. Each produces a "Float". These are case-sensitive, unlike other uses of letters in numeric literals ("1E2", "0XFF", "5J", etc.). * Hy allows complex literals as understood by the constructor for "complex", such as "5+4j". (This is also legal Python, but Hy reads it as a single "Complex", and doesn't otherwise support infix addition or subtraction, whereas Python parses it as an addition expression.) class hy.models.Integer(number, *args, **kwargs) Represents a literal integer ("int"). class hy.models.Float(num, *args, **kwargs) Represents a literal floating-point real number ("float"). class hy.models.Complex(real, imag=0, *args, **kwargs) Represents a literal floating-point complex number ("complex"). If "real" is itself a "complex" object, its imaginary part is extracted and added to the imaginary part of the new model, but "imag", if provided, must be real. Dotted identifiers ------------------ Dotted identifiers are named for their use of the dot character ".", also known as a period or full stop. They don't have their own model type because they're actually syntactic sugar for expressions. Syntax like "foo.bar.baz" is equivalent to "(. foo bar baz)". The general rule is that a dotted identifier looks like two or more symbols (themselves not containing any dots) separated by single dots. The result is an expression with the symbol "." as its first element and the constituent symbols as the remaining elements. A dotted identifier may also begin with one or more dots, as in ".foo.bar" or "..foo.bar", in which case the resulting expression has the appropriate head ("." or ".." or whatever) and the symbol "None" as the following element. Thus, "..foo.bar" is equivalent to "(.. None foo bar)". In the leading-dot case, you may also use only one constitutent symbol. Thus, ".foo" is a legal dotted identifier, and equivalent to "(. None foo)". See the dot macro for what these expressions typically compile to. See also the special behavior for expressions that begin with a dotted identifier that itself begins with a dot. Note that Hy provides definitions of "." and "..." by default, but not "..", "....", ".....", etc., so "..foo.bar" won't do anything useful by default outside of macros that treat it specially, like "import". Symbols ------- Symbols are the catch-all category of identifiers. In most contexts, symbols are compiled to Python variable names, after being mangled. You can create symbol objects with the "quote" operator or by calling the "Symbol" constructor (thus, "Symbol" plays a role similar to the "intern" function in other Lisps). Some example symbols are "hello", "+++", "3fiddy", "$40", "just✈wrong", and "🦑". Dots are only allowed in a symbol if every character in the symbol is a dot. Thus, "a..b" and "a." are neither dotted identifiers nor symbols; they're syntax errors. As a special case, the symbol "..." compiles to the "Ellipsis" object, as in Python. class hy.models.Symbol(s, from_parser=False) Represents a symbol. Symbol objects behave like strings under operations like "get", "len()", and "bool"; in particular, "(bool (hy.models.Symbol "False"))" is true. Use "hy.eval" to evaluate a symbol. Mangling -------- Since the rules for Hy symbols and keywords are much more permissive than the rules for Python identifiers, Hy uses a mangling algorithm to convert its own names to Python-legal names. The steps are as follows: 1. Remove any leading underscores. Underscores are typically the ASCII underscore "_", but they may also be any Unicode character that normalizes (according to NFKC) to "_". Leading underscores have special significance in Python, and Python normalizes all Unicode before this test, so we'll process the remainder of the name and then add the leading underscores back onto the final mangled name. 2. Convert ASCII hyphens ("-") to underscores ("_"). Thus, "foo-bar" becomes "foo_bar". If the name at this step starts with a hyphen, this *first* hyphen is not converted, so that we don't introduce a new leading underscore into the name. Thus "--has-dashes?" becomes "-_has_dashes?" at this step. 3. If the name still isn't Python-legal, make the following changes. A name could be Python-illegal because it contains a character that's never legal in a Python name or it contains a character that's illegal in that position. * Prepend "hyx_" to the name. * Replace each illegal character with "XfooX", where "foo" is the Unicode character name in lowercase, with spaces replaced by underscores and hyphens replaced by "H". Replace leading hyphens and "X" itself the same way. If the character doesn't have a name, use "U" followed by its code point in lowercase hexadecimal. Thus, "green☘" becomes "hyx_greenXshamrockX" and "-_has_dashes" becomes "hyx_XhyphenHminusX_has_dashes". 4. Take any leading underscores removed in the first step, transliterate them to ASCII, and add them back to the mangled name. Thus, "__green☘" becomes "__hyx_greenXshamrockX". 5. Finally, normalize any leftover non-ASCII characters. The result may still not be ASCII (e.g., "α" is already Python-legal and normalized, so it passes through the whole mangling procedure unchanged), but it is now guaranteed that any names are equal as strings if and only if they refer to the same Python identifier. You can invoke the mangler yourself with the function "hy.mangle", and try to undo this (perhaps not quite successfully) with "hy.unmangle". Mangling isn't something you should have to think about often, but you may see mangled names in error messages, the output of "hy2py", etc. A catch to be aware of is that mangling, as well as the inverse "unmangling" operation offered by "hy.unmangle", isn't one-to-one. Two different symbols, like "foo-bar" and "foo_bar", can mangle to the same string and hence compile to the same Python variable. Keywords ======== A string of identifier characters starting with a colon (":") and not containing a dot ("."), such as ":foo", is a "Keyword". Literal keywords are most often used for their special treatment in expressions that aren't macro calls: they set *keyword arguments*, rather than being passed in as values. For example, "(f :foo 3)" calls the function "f" with the parameter "foo" set to "3". The keyword is also mangled at compile-time. To prevent a literal keyword from being treated specially in an expression, you can "quote" the keyword, or you can use it as the value for another keyword argument, as in "(f :foo :bar)". Whereas Python requires all positional arguments in a call to precede all keyword arguments, Hy allows them to mingled, as in "(f 1 :foo 2 3)". This is implemented by simply moving the keyword arguments back, as in "(f 1 3 :foo 2)", with the attendant consequences for order of evaluation (which shouldn't generally be relied upon in Hy). Otherwise, keywords are simple model objects that evaluate to themselves. Users of other Lisps should note that it's often a better idea to use a string than a keyword, because the rest of Python uses strings for cases in which other Lisps would use keywords. In particular, strings are typically more appropriate than keywords as the keys of a dictionary. Notice that "(dict :a 1 :b 2)" is equivalent to "{"a" 1 "b" 2}", which is different from "{:a 1 :b 2}" (see Dictionary literals). The empty keyword ":" is syntactically legal, but you can't compile a function call with an empty keyword argument because of Python limitations. Thus "(foo : 3)" must be rewritten to use runtime unpacking, as in "(foo #** {"" 3})". class hy.models.Keyword(value, from_parser=False) Represents a keyword, such as ":foo". Variables: **name** -- The string content of the keyword, not including the leading ":". No mangling is performed. __bool__() The empty keyword ":" is false. All others are true. __call__(data, default=) Get the element of "data" named "(hy.mangle self.name)". Thus, "(:foo bar)" is equivalent to "(get bar "foo")" (which is different from "(get bar :foo)"; dictionary keys are typically strings, not "hy.models.Keyword" objects). The optional second parameter is a default value; if provided, any "KeyError" from "get" will be caught, and the default returned instead. __lt__(other) Keywords behave like strings under comparison operators, but are incomparable to actual "str" objects. String literals =============== Hy allows double-quoted strings (e.g., ""hello""), but not single- quoted strings like Python. The single-quote character "'" is reserved for preventing the evaluation of a form, (e.g., "'(+ 1 1)"), as in most Lisps (see Additional sugar). Python's so-called triple-quoted strings (e.g., "'''hello'''" and """"hello"""") aren't supported, either. However, in Hy, unlike Python, any string literal can contain newlines; furthermore, Hy has bracket strings. For consistency with Python's triple-quoted strings, all literal newlines in literal strings are read as in ""\n"" (U+000A, line feed) regardless of the newline style in the actual code. String literals support *a variety of backslash escapes*. Unrecognized escape sequences are a syntax error. To create a "raw string" that interprets all backslashes literally, prefix the string with "r", as in "r"slash\not"". By default, all string literals are regarded as sequences of Unicode characters. The result is the model type "String". You may prefix a string literal with "b" to treat it as a sequence of bytes, producing "Bytes" instead. Unlike Python, Hy only recognizes string prefixes ("r", "b", and "f") in lowercase, and doesn't allow the no-op prefix "u". F-strings are a string-like compound construct documented further below. class hy.models.String(s=None, brackets=None) Represents a literal string ("str"). Variables: **brackets** -- The custom delimiter used by the bracket string that parsed to this object, or "None" if it wasn't a bracket string. The outer square brackets and "#" aren't included, so the "brackets" attribute of the literal "#[[hello]]" is the empty string. class hy.models.Bytes Represents a literal bytestring ("bytes"). Bracket strings --------------- Hy supports an alternative form of string literal called a "bracket string" similar to Lua's long brackets. Bracket strings have customizable delimiters, like the here-documents of other languages. A bracket string begins with "#[FOO[" and ends with "]FOO]", where "FOO" is any string not containing "[" or "]", including the empty string. (If "FOO" is exactly "f" or begins with "f-", the bracket string is interpreted as an f-string.) For example: (print #[["That's very kind of yuo [sic]" Tom wrote back.]]) ; "That's very kind of yuo [sic]" Tom wrote back. (print #[==[1 + 1 = 2]==]) ; 1 + 1 = 2 Bracket strings are always raw Unicode strings, and don't allow the "r" or "b" prefixes. A bracket string can contain newlines, but if it begins with one, the newline is removed, so you can begin the content of a bracket string on the line following the opening delimiter with no effect on the content. Any leading newlines past the first are preserved. Sequential forms ================ Sequential forms ("Sequence") are nested forms comprising any number of other forms, in a defined order. class hy.models.Sequence(iterable=(), /) An abstract base class for sequence-like forms. Sequence models can be operated on like tuples: you can iterate over them, index into them, and append them with "+", but you can't add, remove, or replace elements. Appending a sequence to another iterable object reuses the class of the left-hand-side object, which is useful when e.g. you want to concatenate models in a macro. When you're recursively descending through a tree of models, testing a model with "(isinstance x hy.models.Sequence)" is useful for deciding whether to iterate over "x". You can also use the Hyrule function "coll?" for this purpose. Expressions ----------- Expressions ("Expression") are denoted by parentheses: "( … )". The compiler evaluates expressions by checking the first element, called the head. * If the head is a symbol, and the symbol is the name of a currently defined macro, the macro is called. * Exception: if the symbol is also the name of a function in "hy.pyops", and one of the arguments is an "unpack-iterable" form, the "pyops" function is called instead of the macro. This makes reasonable-looking expressions work that would otherwise fail. For example, "(+ #* summands)" is understood as "(hy.pyops.+ #* summands)", because Python provides no way to sum a list of unknown length with a real addition expression. * If the head is itself an expression of the form "(. None …)" (typically produced with a dotted identifier like ".add"), it's used to construct a method call with the element after "None" as the object: thus, "(.add my-set 5)" is equivalent to "((. my-set add) 5)", which becomes "my_set.add(5)" in Python. * Exception: expressions like "((. hy R module-name macro-name) …)", or equivalently "(hy.R.module-name.macro-name …)", get special treatment. They "require" the module "module-name" and call its macro "macro-name", so "(hy.R.foo.bar 1)" is equivalent to "(require foo) (foo.bar 1)", but without bringing "foo" or "foo.bar" into scope. Thus "hy.R" is convenient syntactic sugar for macros you'll only call once in a file, or for macros that you want to appear in the expansion of other macros without having to call "require" in the expansion. As with "hy.I", dots in the module name must be replaced with slashes. * Otherwise, the expression is compiled into a Python-level call, with the head being the calling object. (So, you can call a function that has the same name as a macro with an expression like "((do setv) …)".) The remaining forms are understood as arguments. Use "unpack- iterable" or "unpack-mapping" to break up data structures into individual arguments at runtime. The empty expression "()" is legal at the reader level, but has no inherent meaning. Trying to compile it is an error. For the empty tuple, use "#()". class hy.models.Expression(iterable=(), /) Represents a parenthesized Hy expression. List, tuple, and set literals ----------------------------- * Literal "list"s ("List") are denoted by "[ … ]". * Literal "tuple"s ("Tuple") are denoted by "#( … )". * Literal "set"s ("Set") are denoted by "#{ … }". class hy.models.List(iterable=(), /) Represents a literal "list". Many macros use this model type specially, for something other than defining a "list". For example, "defn" expects its function parameters as a square-bracket-delimited list, and "for" expects a list of iteration clauses. class hy.models.Tuple(iterable=(), /) Represents a literal "tuple". class hy.models.Set(iterable=(), /) Represents a literal "set". Unlike actual sets, the model retains duplicates and the order of elements. Dictionary literals ------------------- Literal dictionaries ("dict", "Dict") are denoted by "{ … }". Even- numbered child forms (counting the first as 0) become the keys whereas odd-numbered child forms become the values. For example, "{"a" 1 "b" 2}" produces a dictionary mapping ""a"" to "1" and ""b"" to "2". Trying to compile a "Dict" with an odd number of child models is an error. As in Python, calling "dict" with keyword arguments may be more convenient than using a literal dictionary when all the keys are strings. Compare the following alternatives: (dict :a 1 :b 2 :c 3 :d 4 :e 5) {"a" 1 "b" 2 "c" 3 "d" 4 "e" 5} class hy.models.Dict(iterable=(), /) Represents a literal "dict". "keys", "values", and "items" methods are provided, each returning a list, although this model type does none of the normalization of a real "dict". In the case of an odd number of child models, "keys" returns the last child whereas "values" and "items" ignore it. Format strings -------------- A format string (or "f-string", or "formatted string literal") is a string literal with embedded code, possibly accompanied by formatting commands. The result is an "FString", Hy f-strings work much like *Python f-strings* except that the embedded code is in Hy rather than Python. (print f"The sum is {(+ 1 1)}.") ; => The sum is 2. Since "=", "!", and ":" are identifier characters in Hy, Hy decides where the code in a replacement field ends (and any debugging "=", conversion specifier, or format specifier begins) by parsing exactly one form. You can use "do" to combine several forms into one, as usual. Whitespace may be necessary to terminate the form: (setv foo "a") (print f"{foo:x<5}") ; => NameError: name 'hyx_fooXcolonXxXlessHthan_signX5' is not defined (print f"{foo :x<5}") ; => axxxx Unlike Python, whitespace is allowed between a conversion and a format specifier. Also unlike Python, comments and backslashes are allowed in replacement fields. The same reader is used for the form to be evaluated as for elsewhere in the language. Thus e.g. "f"{"a"}"" is legal, and equivalent to ""a"". class hy.models.FString(s=None, brackets=None) Represents a format string as an iterable collection of "hy.models.String" and "hy.models.FComponent". The design mimics "ast.JoinedStr". Variables: **brackets** -- As in "hy.models.String". class hy.models.FComponent(s=None, conversion=None) An analog of "ast.FormattedValue". The first node in the contained sequence is the value being formatted. The rest of the sequence contains the nodes in the format spec (if any). Additional sugar ================ Syntactic sugar is available to construct two-item expressions with certain heads. When the sugary characters are encountered by the reader, a new expression is created with the corresponding macro name as the first element and the next parsed form as the second. No parentheses are required. Thus, since "'" is short for "quote", "'FORM" is read as "(quote FORM)". Whitespace is allowed, as in "' FORM". This is all resolved at the reader level, so the model that gets produced is the same whether you take your code with sugar or without. +----------------------------+------------------+ | Macro | Syntax | |============================|==================| | "quote" | "'FORM" | +----------------------------+------------------+ | "quasiquote" | "`FORM" | +----------------------------+------------------+ | "unquote" | "~FORM" | +----------------------------+------------------+ | "unquote-splice" | "~@FORM" | +----------------------------+------------------+ | "unpack-iterable" | "#* FORM" | +----------------------------+------------------+ | "unpack-mapping" | "#** FORM" | +----------------------------+------------------+ Reader macros ============= A hash ("#") followed by a symbol invokes the reader macro named by the symbol. (Trying to call an undefined reader macro is a syntax error.) Parsing of the remaining source code is under control of the reader macro until it returns. Tutorial ******** [image: Karen Rustard's Cuddles][image]Hy's mascot, Cuddles the cuttlefish. This chapter provides a quick introduction to Hy. It assumes a basic background in programming, but no specific prior knowledge of Python or Lisp. Contents ^^^^^^^^ * Lisp-stick on a Python * Literals * Basic operations * Functions, classes, and modules * Macros * Recommended libraries * Next steps Lisp-stick on a Python ====================== Let's start with the classic: (print "Hy, world!") This program calls the "print()" function, which, like all of Python's *built-in functions*, is available in Hy. All of Python's *binary and unary operators* are available, too, although "==" is spelled "=" in deference to Lisp tradition. Here's how we'd use the addition operator "+": (+ 1 3) This code returns "4". It's equivalent to "1 + 3" in Python and many other languages. Languages in the Lisp family, including Hy, use a prefix syntax: "+", just like "print" or "sqrt", appears before all of its arguments. The call is delimited by parentheses, but the opening parenthesis appears before the operator being called instead of after it, so instead of "sqrt(2)", we write "(sqrt 2)". Multiple arguments, such as the two integers in "(+ 1 3)", are separated by whitespace. Many operators, including "+", allow more than two arguments: "(+ 1 2 3)" is equivalent to "1 + 2 + 3". Here's a more complex example: (- (* (+ 1 3 88) 2) 8) This code returns "176". Why? You can see the infix equivalent with the command "echo "(- (* (+ 1 3 88) 2) 8)" | hy2py", which returns the Python code corresponding to the given Hy code. Or you can pass the " --spy" option to Hy when starting the interactive read-eval-print loop (REPL), which shows the Python equivalent of each input line before the result. (To translate in the other direction, from Python to Hy, try the external program py2hy.) The infix equivalent in this case is: ((1 + 3 + 88) * 2) - 8 To evaluate this infix expression, you'd of course evaluate the innermost parenthesized expression first and work your way outwards. The same goes for Lisp. Here's what we'd get by evaluating the above Hy code one step at a time: (- (* (+ 1 3 88) 2) 8) (- (* 92 2) 8) (- 184 8) 176 The basic unit of Lisp syntax, which is similar to a C or Python expression, is the **form**. "92", "*", and "(* 92 2)" are all forms. A Lisp program consists of a sequence of forms nested within forms. Forms are typically separated from each other by whitespace, but some forms, such as string literals (""Hy, world!""), can contain whitespace themselves. An expression is a form enclosed in parentheses; its first child form, called the **head**, determines what the expression does, and should generally be a function or macro. *Functions*, the most ordinary sort of head, constitute reusable pieces of code that can take in arguments and return a value. Macros (described in more detail below) are a special kind of function that's executed at compile-time and returns code to be executed at run-time. Comments start with a ";" character and continue till the end of the line. A comment is functionally equivalent to whitespace. (setv password "susan") ; My daughter's name Although "#" isn't a comment character in Hy, a Hy program can begin with a shebang line, which Hy itself will ignore: #!/usr/bin/env hy (print "Make me executable, and run me!") Literals ======== Hy has literal syntax for all of the same data types that Python does. Here's an example of Hy code for each type and the Python equivalent. +----------------+------------------+-------------------+ | Hy | Python | Type | |================|==================|===================| | "1" | "1" | "int" | +----------------+------------------+-------------------+ | "1.2" | "1.2" | "float" | +----------------+------------------+-------------------+ | "4j" | "4j" | "complex" | +----------------+------------------+-------------------+ | "True" | "True" | "bool" | +----------------+------------------+-------------------+ | "None" | "None" | "NoneType" | +----------------+------------------+-------------------+ | ""hy"" | "'hy'" | "str" | +----------------+------------------+-------------------+ | "b"hy"" | "b'hy'" | "bytes" | +----------------+------------------+-------------------+ | "#(1 2 3)" | "(1, 2, 3)" | "tuple" | +----------------+------------------+-------------------+ | "[1 2 3]" | "[1, 2, 3]" | "list" | +----------------+------------------+-------------------+ | "#{1 2 3}" | "{1, 2, 3}" | "set" | +----------------+------------------+-------------------+ | "{1 2 3 4}" | "{1: 2, 3: 4}" | "dict" | +----------------+------------------+-------------------+ The Hy REPL prints output in Hy syntax by default, with the function "hy.repr": => [1 2 3] [1 2 3] But if you start Hy like this: $ hy --repl-output-fn=repr the REPL will use Python's native "repr()" function instead, so you'll see values in Python syntax: => [1 2 3] [1, 2, 3] Basic operations ================ Set variables with "setv": (setv zone-plane 8) Access the elements of a list, dictionary, or other data structure with "get": (setv fruit ["apple" "banana" "cantaloupe"]) (print (get fruit 0)) ; => apple (setv (get fruit 1) "durian") (print (get fruit 1)) ; => durian Access a range of elements in an ordered structure with "cut": (print (cut "abcdef" 1 4)) ; => bcd Conditional logic can be built with "if": (if (= 1 1) (print "Math works. The universe is safe.") (print "Math has failed. The universe is doomed.")) As in this example, "if" is called like "(if CONDITION THEN ELSE)". It executes and returns the form "THEN" if "CONDITION" is true (according to "bool") and "ELSE" otherwise. What if you want to use more than form in place of the "THEN" or "ELSE" clauses, or in place of "CONDITION", for that matter? Use the macro "do" (known more traditionally in Lisp as "progn"), which combines several forms into one, returning the last: (if (do (print "Let's check.") (= 1 1)) (do (print "Math works.") (print "The universe is safe.")) (do (print "Math has failed.") (print "The universe is doomed."))) For branching on more than one case, try "cond": (setv somevar 33) (cond (> somevar 50) (print "That variable is too big!") (< somevar 10) (print "That variable is too small!") True (print "That variable is jussssst right!")) The macro "(when CONDITION THEN-1 THEN-2 …)" is shorthand for "(if CONDITION (do THEN-1 THEN-2 …) None)". Hy's basic loops are "while" and "for": (setv x 3) (while (> x 0) (print x) (setv x (- x 1))) ; => 3 2 1 (for [x [1 2 3]] (print x)) ; => 1 2 3 A more functional way to iterate is provided by the comprehension forms such as "lfor". Whereas "for" always returns "None", "lfor" returns a list with one element per iteration. (print (lfor x [1 2 3] (* x 2))) ; => [2, 4, 6] Functions, classes, and modules =============================== Define named functions with "defn": (defn fib [n] (if (< n 2) n (+ (fib (- n 1)) (fib (- n 2))))) (print (fib 8)) ; => 21 Define anonymous functions with "fn": (print (list (filter (fn [x] (% x 2)) (range 10)))) ; => [1, 3, 5, 7, 9] Special symbols in the parameter list of "defn" or "fn" allow you to indicate optional arguments, provide default values, and collect unlisted arguments: (defn test [a b [c None] [d "x"] #* e] [a b c d e]) (print (test 1 2)) ; => [1, 2, None, 'x', ()] (print (test 1 2 3 4 5 6 7)) ; => [1, 2, 3, 4, (5, 6, 7)] Set a function parameter by name with a ":keyword": (test 1 2 :d "y") ; => [1, 2, None, 'y', ()] Keyword arguments may be placed before or among positional arguments, with the same effect as putting all the positional arguments first: (test 1 :d "y" 2) ; => [1, 2, None, 'y', ()] You can unpack iterable objects into positional arguments with "#*" ("unpack-iterable"), or dictionary-like objects into keyword arguments with "#**" ("unpack-mapping"): (setv x [1 2 3]) (setv y {"d" 4}) (test #* x #** y) ; => [1, 2, 3, 4, ()] Note that unlike Python, Hy doesn't always evaluate function arguments (or the items in a literal list, or the items in a literal dictionary, etc.) in the order they appear in the code. But you can always force a particular evaluation order with "do", or with other macros that provide an implicit "do", like "when" or "fn". Define classes with "defclass": (defclass FooBar [] (defn __init__ [self x] (setv self.x x)) (defn get-x [self] self.x)) Here we create a new instance "fb" of "FooBar" and access its attributes with a dotted identifier or the dot macro: (setv fb (FooBar 15)) (print fb.x) ; => 15 (print (. fb x)) ; => 15 (print (. fb (get-x)) ; => 15 (print (.get-x fb)) ; => 15 (print (fb.get-x)) ; => 15 Note that syntax like "fb.x" and "fb.get-x" only works when the object being invoked ("fb", in this case) is a simple variable name. To get an attribute or call a method of an arbitrary form "FORM", you must use one of the other options, such as "(. FORM x)" or "(.get-x FORM)", or call "getattr()". Access an external module, whether written in Python or Hy, with "import": (import math) (print (math.sqrt 2)) ; => 1.4142135623730951 Or use the one-shot import syntax "hy.I": (print (hy.I.math.sqrt 2)) Python can import a Hy module like any other module so long as Hy itself has been imported first, which, of course, must have already happened if you're running a Hy program. Macros ====== Macros are the basic metaprogramming tool of Lisp. A macro is a function that is called at compile time (i.e., when a Hy program is being translated to Python "ast" objects) and returns code, which becomes part of the final program. Here's a simple example: (print "Executing") (defmacro m [] (print "Now for a slow computation") (setv x (% (** 10 10 7) 3)) (print "Done computing") x) (print "Value:" (m)) (print "Done executing") If you run this program twice in a row, you'll see this: $ hy example.hy Now for a slow computation Done computing Executing Value: 1 Done executing $ hy example.hy Executing Value: 1 Done executing The slow computation is performed while compiling the program on its first invocation. Only after the whole program is compiled does normal execution begin from the top, printing "Executing". When the program is called a second time, it is run from the previously compiled bytecode, which is equivalent to simply: (print "Executing") (print "Value:" 1) (print "Done executing") Our macro "m" has an especially simple return value, an integer ("int"), which at compile-time is converted to an integer model ("hy.models.Integer"). In general, macros can return arbitrary Hy models to be executed as code. There are several helper macros that make it easy to construct forms programmatically, such as "quote" ("'"), "quasiquote" ("`"), "unquote" ("~"), "unquote-splice" ("~@"), and "defmacro!". The previous chapter has a simple example of using "`" and "~@" to define a new control construct "do-while". What if you want to use a macro that's defined in a different module? "import" won't help, because it merely translates to a Python "import" statement that's executed at run-time, and macros are expanded at compile-time, that is, during the translation from Hy to Python. Instead, use "require", which imports the module and makes macros available at compile-time. "require" uses the same syntax as "import". (require some-module.macros) (some-module.macros.rev (1 2 3 +)) ; => 6 Hy also supports reader macros, which are similar to ordinary macros, but operate on raw source text rather than pre-parsed Hy forms. They can choose how much of the source code to consume after the point they are called, and return any code. Thus, reader macros can add entirely new syntax to Hy. For example, you could add a literal notation for Python's "decimal.Decimal" class like so: (defreader d (.slurp-space &reader) `(hy.I.decimal.Decimal ~(.read-ident &reader))) (print (repr #d .1)) ; => Decimal('0.1') (import fractions [Fraction]) (print (Fraction #d .1)) ; => 1/10 ;; Contrast with the normal floating-point .1: (print (Fraction .1)) ; => 3602879701896397/36028797018963968 "require" can pull in a reader macro defined in a different module with syntax like "(require mymodule :readers [d])". Recommended libraries ===================== Hyrule is Hy's standard utility library. It provides a variety of functions and macros that are useful for writing Hy programs. (import hyrule [inc]) (list (map inc [1 2 3])) ; => [2 3 4] (require hyrule [case]) (setv x 2) (case x 1 "a" 2 "b" 3 "c") ; => "b" toolz and its Cython variant cytoolz provide lots of utilities for functional programming and working with iterables. (import toolz [partition]) (list (partition 2 [1 2 3 4 5 6])) ; => [#(1 2) #(3 4) #(5 6)] metadict allows you to refer to the elements of a dictionary as attributes. This is handy when frequently referring to elements with constant strings as keys, since plain indexing is a bit verbose in Hy. (import metadict [MetaDict]) (setv d (MetaDict)) (setv d.foo 1) ; i.e., (setv (get d "foo") 1) d.foo ; i.e., (get d "foo") ; => 1 (list (.keys d)) ; => ["foo"] Next steps ========== You now know enough to be dangerous with Hy. You may now smile villainously and sneak off to your Hydeaway to do unspeakable things. Refer to Python's documentation for the details of Python semantics. In particular, *the Python tutorial* can be helpful even if you have no interest in writing your own Python code, because it will introduce you to the semantics, and you'll need a reading knowledge of Python syntax to understand example code for Python libraries. Refer to the rest of this manual for Hy-specific features. See the wiki for tips on getting Hy to work with other software. For an official full-blown example Hy program, see Infinitesimal Quest 2 + ε. Why Hy? ******* Hy (or "Hylang" for long; named after the insect order Hymenoptera, since Paul Tagliamonte was studying swarm behavior when he created the language) is a multi-paradigm general-purpose programming language in the Lisp family. It's implemented as a kind of alternative syntax for Python. Compared to Python, Hy offers a variety of new features, generalizations, and syntactic simplifications, as would be expected of a Lisp. Compared to other Lisps, Hy provides direct access to Python's built-ins and third-party Python libraries, while allowing you to freely mix imperative, functional, and object-oriented styles of programming. Contents ^^^^^^^^ * Hy versus Python * Hy versus other Lisps * What Hy is not Hy versus Python ================ The first thing a Python programmer will notice about Hy is that it has Lisp's traditional parenthesis-heavy prefix syntax in place of Python's C-like infix syntax. For example, print("The answer is", 2 + object.method(arg)) could be written (print "The answer is" (+ 2 (.method object arg))) in Hy. Consequently, Hy is free-form: structure is indicated by punctuation rather than whitespace, making it convenient for command- line use. As in other Lisps, the value of a simplistic syntax is that it facilitates Lisp's signature feature: metaprogramming through macros, which are functions that manipulate code objects at compile time to produce new code objects, which are then executed as if they had been part of the original code. In fact, Hy allows arbitrary computation at compile-time. For example, here's a simple macro that implements a C-style do-while loop, which executes its body for as long as the condition is true, but at least once. (defmacro do-while [condition #* body] `(do ~@body (while ~condition ~@body))) (setv x 0) (do-while x (print "This line is executed once.")) Hy also removes Python's restrictions on mixing expressions and statements, allowing for more direct and functional code. For example, Python doesn't allow "with" blocks, which close a resource once you're done using it, to return values. They can only execute a set of statements: with open("foo") as o: f1 = o.read() with open("bar") as o: f2 = o.read() print(len(f1) + len(f2)) In Hy, "with" returns the value of its last body form, so you can use it like an ordinary function call: (print (+ (len (with [o (open "foo")] (.read o))) (len (with [o (open "bar")] (.read o))))) To be even more concise, you can put a "with" form in a "gfor": (print (sum (gfor filename ["foo" "bar"] (len (with [o (open filename)] (.read o)))))) Finally, Hy offers several generalizations to Python's binary operators. Operators can be given more than two arguments (e.g., "(+ 1 2 3)"), including augmented assignment operators (e.g., "(+= x 1 2 3)"). They are also provided as ordinary first-class functions of the same name, allowing them to be passed to higher-order functions: "(sum xs)" could be written "(reduce + xs)", after importing the function "+" from the module "hy.pyops". The Hy compiler works by reading Hy source code into Hy model objects and compiling them into Python abstract syntax tree ("ast") objects. Python AST objects can then be compiled and run by Python itself, byte-compiled for faster execution later, or rendered into Python source code. You can mix Python and Hy code in the same project, or even the same file, which can be a good way to get your feet wet in Hy. Hy versus other Lisps ===================== At run-time, Hy is essentially Python code. Thus, while Hy's design owes a lot to Clojure, it is more tightly coupled to Python than Clojure is to Java; a better analogy is CoffeeScript's relationship with JavaScript. Python's built-in *functions* and *data structures* are directly available: (print (int "deadbeef" :base 16)) ; 3735928559 (print (len [1 10 100])) ; 3 The same goes for third-party Python libraries from PyPI and elsewhere. Here's a tiny CherryPy web application in Hy: (import cherrypy) (defclass HelloWorld [] (defn [cherrypy.expose] index [self] "Hello World!")) (cherrypy.quickstart (HelloWorld)) You can even run Hy on PyPy for a particularly speedy Lisp. Like all Lisps, Hy is homoiconic. Its syntax is represented not with cons cells or with Python's basic data structures, but with simple subclasses of Python's basic data structures called models. Using models in place of plain "list"s, "set"s, and so on has two purposes: models can keep track of their line and column numbers for the benefit of error messages, and models can represent syntactic features that the corresponding primitive type can't, such as the order in which elements appear in a set literal. However, models can be concatenated and indexed just like plain lists, and you can return ordinary Python types from a macro or give them to "hy.eval" and Hy will automatically promote them to models. Hy takes much of its semantics from Python. For example, functions use the same namespace as objects that aren't functions, so a variable named "globals" can shadow the Python built-in function "globals()". In general, any Python code should be possible to literally translate to Hy. At the same time, Hy goes to some lengths to allow you to do typical Lisp things that aren't straightforward in Python. For example, Hy provides the aforementioned mixing of statements and expressions, name mangling that transparently converts symbols with names like "valid?" to Python-legal identifiers, and a "let" macro to provide block-level scoping in place of Python's usual function-level scoping. What Hy is not ============== Hy isn't minimal or elegant. Hy is big and ugly and proud of it; it's an unopinionated big-tent language that lets you do what you want. It has all of Python's least-motivated semantic features, plus more features, plus various kinds of syntactic sugar. (The syntax isn't as complex as Python's, but there are a lot of details beyond plain old S-expressions.) If you're interested in a more small-and-beautiful approach to Lisp, in the style of Scheme, check out Hissp, another Lisp embedded in Python that was created by a Hy developer. Also, Hy isn't a reimplementation of an older Lisp. It is its own language. It looks kind of like Clojure and kind of like Common Lisp, but nontrivial programs that run in one of these langauges can't be expected to run on another unaltered.