(.module: [library [lux {"-" Location Code Label or and function if cond undefined for comment not int try ++ --} [control [pipe {"+" case>}]] [data ["[0]" text ["%" format {"+" format}]] [collection ["[0]" list ("[1]#[0]" functor mix)]]] [macro ["[0]" template]] [math [number ["i" int] ["f" frac]]] [type abstract]]]) (def: expression (text.enclosed ["(" ")"])) (def: element (text.enclosed ["[" "]"])) (def: nested (-> Text Text) (|>> (format text.new_line) (text.replaced text.new_line (format text.new_line text.tab)))) (abstract: .public (Code brand) Text (def: .public code (-> (Code Any) Text) (|>> :representation)) (template [ +] [(with_expansions [ (template.identifier [ "'"])] (abstract: ( brand) Any) (`` (type: .public (|> Any (~~ (template.spliced +))))))] [Expression [Code]] [Computation [Expression' Code]] [Location [Computation' Expression' Code]] [Statement [Code]] ) (template [ +] [(with_expansions [ (template.identifier [ "'"])] (abstract: Any) (`` (type: .public (|> (~~ (template.spliced +))))))] [Var [Location' Computation' Expression' Code]] [Access [Location' Computation' Expression' Code]] [Literal [Computation' Expression' Code]] [Loop [Statement' Code]] [Label [Code]] ) (template [ ] [(def: .public Literal (:abstraction ))] [null "null"] [undefined "undefined"] ) (def: .public boolean (-> Bit Literal) (|>> (case> #0 "false" #1 "true") :abstraction)) (def: .public (number value) (-> Frac Literal) (:abstraction (.cond (f.not_a_number? value) "NaN" (f.= f.positive_infinity value) "Infinity" (f.= f.negative_infinity value) "-Infinity" ... else (|> value %.frac ..expression)))) (def: safe (-> Text Text) (`` (|>> (~~ (template [ ] [(text.replaced )] ["\\" "\"] ["\t" text.tab] ["\v" text.vertical_tab] ["\0" text.null] ["\b" text.back_space] ["\f" text.form_feed] ["\n" text.new_line] ["\r" text.carriage_return] [(format "\" text.double_quote) text.double_quote] )) ))) (def: .public string (-> Text Literal) (|>> ..safe (text.enclosed [text.double_quote text.double_quote]) :abstraction)) (def: argument_separator ", ") (def: field_separator ": ") (def: statement_suffix ";") (def: .public array (-> (List Expression) Computation) (|>> (list#each ..code) (text.interposed ..argument_separator) ..element :abstraction)) (def: .public var (-> Text Var) (|>> :abstraction)) (def: .public (at index array_or_object) (-> Expression Expression Access) (:abstraction (format (:representation array_or_object) (..element (:representation index))))) (def: .public (the field object) (-> Text Expression Access) (:abstraction (format (:representation object) "." field))) (def: .public (apply/* function inputs) (-> Expression (List Expression) Computation) (|> inputs (list#each ..code) (text.interposed ..argument_separator) ..expression (format (:representation function)) :abstraction)) (def: .public (do method inputs object) (-> Text (List Expression) Expression Computation) (apply/* (..the method object) inputs)) (def: .public object (-> (List [Text Expression]) Computation) (|>> (list#each (.function (_ [key val]) (format (:representation (..string key)) ..field_separator (:representation val)))) (text.interposed ..argument_separator) (text.enclosed ["{" "}"]) ..expression :abstraction)) (def: .public (, pre post) (-> Expression Expression Computation) (|> (format (:representation pre) ..argument_separator (:representation post)) ..expression :abstraction)) (def: .public (then pre post) (-> Statement Statement Statement) (:abstraction (format (:representation pre) text.new_line (:representation post)))) (def: block (-> Statement Text) (let [close (format text.new_line "}")] (|>> :representation ..nested (text.enclosed ["{" close])))) (def: .public (function! name inputs body) (-> Var (List Var) Statement Statement) (|> body ..block (format "function " (:representation name) (|> inputs (list#each ..code) (text.interposed ..argument_separator) ..expression) " ") :abstraction)) (def: .public (function name inputs body) (-> Var (List Var) Statement Computation) (|> (..function! name inputs body) :representation ..expression :abstraction)) (def: .public (closure inputs body) (-> (List Var) Statement Computation) (|> body ..block (format "function" (|> inputs (list#each ..code) (text.interposed ..argument_separator) ..expression) " ") ..expression :abstraction)) (template [ ] [(def: .public ( param subject) (-> Expression Expression Computation) (|> (format (:representation subject) " " " " (:representation param)) ..expression :abstraction))] [= "==="] [< "<"] [<= "<="] [> ">"] [>= ">="] [+ "+"] [- "-"] [* "*"] [/ "/"] [% "%"] [left_shift "<<"] [arithmetic_right_shift ">>"] [logic_right_shift ">>>"] [or "||"] [and "&&"] [bit_xor "^"] [bit_or "|"] [bit_and "&"] ) (template [ ] [(def: .public (-> Expression Computation) (|>> :representation (text.prefix ) ..expression :abstraction))] [not "!"] [bit_not "~"] [opposite "-"] ) (template [ ] [... A 32-bit integer expression. (def: .public ( value) (-> Computation) (:abstraction (..expression (format ( value) "|0"))))] [to_i32 Expression :representation] [i32 Int %.int] ) (def: .public (int value) (-> Int Literal) (:abstraction (.if (i.< +0 value) (%.int value) (%.nat (.nat value))))) (def: .public (? test then else) (-> Expression Expression Expression Computation) (|> (format (:representation test) " ? " (:representation then) " : " (:representation else)) ..expression :abstraction)) (def: .public type_of (-> Expression Computation) (|>> :representation (format "typeof ") ..expression :abstraction)) (def: .public (new constructor inputs) (-> Expression (List Expression) Computation) (|> (format "new " (:representation constructor) (|> inputs (list#each ..code) (text.interposed ..argument_separator) ..expression)) ..expression :abstraction)) (def: .public statement (-> Expression Statement) (|>> :representation (text.suffix ..statement_suffix) :abstraction)) (def: .public use_strict Statement (:abstraction (format text.double_quote "use strict" text.double_quote ..statement_suffix))) (def: .public (declare name) (-> Var Statement) (:abstraction (format "var " (:representation name) ..statement_suffix))) (def: .public (define name value) (-> Var Expression Statement) (:abstraction (format "var " (:representation name) " = " (:representation value) ..statement_suffix))) (def: .public (set name value) (-> Location Expression Statement) (:abstraction (format (:representation name) " = " (:representation value) ..statement_suffix))) (def: .public (throw message) (-> Expression Statement) (:abstraction (format "throw " (:representation message) ..statement_suffix))) (def: .public (return value) (-> Expression Statement) (:abstraction (format "return " (:representation value) ..statement_suffix))) (def: .public (delete value) (-> Location Statement) (:abstraction (format "delete " (:representation value) ..statement_suffix))) (def: .public (if test then! else!) (-> Expression Statement Statement Statement) (:abstraction (format "if(" (:representation test) ") " (..block then!) " else " (..block else!)))) (def: .public (when test then!) (-> Expression Statement Statement) (:abstraction (format "if(" (:representation test) ") " (..block then!)))) (def: .public (while test body) (-> Expression Statement Loop) (:abstraction (format "while(" (:representation test) ") " (..block body)))) (def: .public (do_while test body) (-> Expression Statement Loop) (:abstraction (format "do " (..block body) " while(" (:representation test) ")" ..statement_suffix))) (def: .public (try body [exception catch]) (-> Statement [Var Statement] Statement) (:abstraction (format "try " (..block body) " catch(" (:representation exception) ") " (..block catch)))) (def: .public (for var init condition update iteration) (-> Var Expression Expression Expression Statement Loop) (:abstraction (format "for(" (:representation (..define var init)) " " (:representation condition) ..statement_suffix " " (:representation update) ")" (..block iteration)))) (def: .public label (-> Text Label) (|>> :abstraction)) (def: .public (with_label label loop) (-> Label Loop Statement) (:abstraction (format (:representation label) ": " (:representation loop)))) (template [ <0> <1>] [(def: .public <0> Statement (:abstraction (format ..statement_suffix))) (def: .public (<1> label) (-> Label Statement) (:abstraction (format " " (:representation label) ..statement_suffix)))] ["break" break break_at] ["continue" continue continue_at] ) (template [ ] [(def: .public (-> Location Expression) (|>> :representation (text.suffix ) :abstraction))] [++ "++"] [-- "--"] ) (def: .public (comment commentary on) (All (_ kind) (-> Text (Code kind) (Code kind))) (:abstraction (format "/* " commentary " */" " " (:representation on)))) (def: .public (switch input cases default) (-> Expression (List [(List Literal) Statement]) (Maybe Statement) Statement) (:abstraction (format "switch (" (:representation input) ") " (|> (format (|> cases (list#each (.function (_ [when then]) (format (|> when (list#each (|>> :representation (text.enclosed ["case " ":"]))) (text.interposed text.new_line)) (..nested (:representation then))))) (text.interposed text.new_line)) text.new_line (case default {.#Some default} (format "default:" (..nested (:representation default))) {.#None} "")) :abstraction ..block)))) ) (def: .public (cond clauses else!) (-> (List [Expression Statement]) Statement Statement) (list#mix (.function (_ [test then!] next!) (..if test then! next!)) else! (list.reversed clauses))) (template [ + + +] [(`` (def: .public ( function) (-> Expression (~~ (template.spliced +)) Computation) (.function (_ (~~ (template.spliced +))) (..apply/* function (list (~~ (template.spliced +))))))) (`` (template [ ] [(def: .public ( (..var )))] (~~ (template.spliced +))))] [apply/1 [_0] [Expression] [[not_a_number? "isNaN"]]] [apply/2 [_0 _1] [Expression Expression] []] [apply/3 [_0 _1 _2] [Expression Expression Expression] []] )