(.module: [library [lux (#- Location Code static int if cond function or and not comment local global) ["@" target] [abstract [equivalence (#+ Equivalence)] [hash (#+ Hash)] ["." enum]] [control [pipe (#+ case> cond> new>)] [parser ["<.>" code]]] [data ["." text ["%" format (#+ format)]] [collection ["." list ("#\." functor fold)]]] [macro [syntax (#+ syntax:)] ["." template] ["." code]] [math [number ["n" nat] ["f" frac]]] [type abstract]]]) (def: input_separator ", ") (def: statement_suffix ";") (def: nested (-> Text Text) (.let [nested_new_line (format text.new_line text.tab)] (|>> (format text.new_line) (text.replaced text.new_line nested_new_line)))) (abstract: .public (Code brand) {} Text (implementation: .public code_equivalence (All [brand] (Equivalence (Code brand))) (def: (= reference subject) (\ text.equivalence = (:representation reference) (:representation subject)))) (implementation: .public code_hash (All [brand] (Hash (Code brand))) (def: &equivalence ..code_equivalence) (def: hash (|>> :representation (\ text.hash hash)))) (def: .public manual (-> Text Code) (|>> :abstraction)) (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]] [Var [Location' Computation' Expression' Code]] [LVar [Var' Location' Computation' Expression' Code]] [Statement [Code]] ) (template [ +] [(with_expansions [ (template.identifier [ "'"])] (abstract: .public {} Any) (`` (type: .public (|> (~~ (template.spliced +))))))] [Literal [Computation' Expression' Code]] [Access [Location' Computation' Expression' Code]] [GVar [Var' Location' Computation' Expression' Code]] [IVar [Var' Location' Computation' Expression' Code]] [SVar [Var' Location' Computation' Expression' Code]] [LVar* [LVar' Var' Location' Computation' Expression' Code]] [LVar** [LVar' Var' Location' Computation' Expression' Code]] ) (template [ ] [(def: .public (-> Text ) (|>> (format ) :abstraction))] [GVar "$" global] [IVar "@" instance] [SVar "@@" static] ) (def: .public local (-> Text LVar) (|>> :abstraction)) (template [ ] [(template [ ] [(def: .public (-> ) (|>> :representation (format ) :abstraction))] [ LVar ] [ Expression Computation] )] [LVar* "*" variadic splat] [LVar** "**" variadic_kv double_splat] ) (template [ ] [(def: .public (..global ))] ["@" latest_error] ["_" last_string_read] ["." last_line_number_read] ["&" last_string_matched] ["~" last_regexp_match] ["=" case_insensitivity_flag] ["/" input_record_separator] ["\" output_record_separator] ["0" script_name] ["$" process_id] ["?" exit_status] ) (template [ ] [(def: .public (..local ))] ["ARGV" command_line_arguments] ) (def: .public nil Literal (:abstraction "nil")) (def: .public bool (-> Bit Literal) (|>> (case> #0 "false" #1 "true") :abstraction)) (def: safe (-> Text Text) (`` (|>> (~~ (template [ ] [(text.replaced )] ["\" "\\"] [text.tab "\t"] [text.vertical_tab "\v"] [text.null "\0"] [text.back_space "\b"] [text.form_feed "\f"] [text.new_line "\n"] [text.carriage_return "\r"] [text.double_quote (format "\" text.double_quote)] )) ))) (template [ ] [(def: .public (-> Literal) (|>> :abstraction))] [%.int int Int (<|)] [%.text string Text ..safe] [(<|) symbol Text (format ":")] ) (def: .public float (-> Frac Literal) (|>> (cond> [(f.= f.positive_infinity)] [(new> "(+1.0/0.0)" [])] [(f.= f.negative_infinity)] [(new> "(-1.0/0.0)" [])] [(f.= f.not_a_number)] [(new> "(+0.0/-0.0)" [])] ... else [%.frac]) :abstraction)) (def: .public (array_range from to array) (-> Expression Expression Expression Computation) (|> (format (:representation from) ".." (:representation to)) (text.enclosed ["[" "]"]) (format (:representation array)) :abstraction)) (def: .public array (-> (List Expression) Literal) (|>> (list\map (|>> :representation)) (text.join_with ..input_separator) (text.enclosed ["[" "]"]) :abstraction)) (def: .public hash (-> (List [Expression Expression]) Literal) (|>> (list\map (.function (_ [k v]) (format (:representation k) " => " (:representation v)))) (text.join_with ..input_separator) (text.enclosed ["{" "}"]) :abstraction)) (def: .public (apply/* args func) (-> (List Expression) Expression Computation) (|> args (list\map (|>> :representation)) (text.join_with ..input_separator) (text.enclosed ["(" ")"]) (format (:representation func)) :abstraction)) (def: .public (apply_lambda/* args lambda) (-> (List Expression) Expression Computation) (|> args (list\map (|>> :representation)) (text.join_with ..input_separator) (text.enclosed ["[" "]"]) (format (:representation lambda)) :abstraction)) (def: .public (the field object) (-> Text Expression Access) (:abstraction (format (:representation object) "." field))) (def: .public (nth idx array) (-> Expression Expression Access) (|> (:representation idx) (text.enclosed ["[" "]"]) (format (:representation array)) :abstraction)) (def: .public (? test then else) (-> Expression Expression Expression Computation) (|> (format (:representation test) " ? " (:representation then) " : " (:representation else)) (text.enclosed ["(" ")"]) :abstraction)) (def: .public statement (-> Expression Statement) (|>> :representation (text.suffix ..statement_suffix) :abstraction)) (def: .public (then pre! post!) (-> Statement Statement Statement) (:abstraction (format (:representation pre!) text.new_line (:representation post!)))) (def: .public (set vars value) (-> (List Location) Expression Statement) (:abstraction (format (|> vars (list\map (|>> :representation)) (text.join_with ..input_separator)) " = " (:representation value) ..statement_suffix))) (def: (block content) (-> Text Text) (format content text.new_line "end" ..statement_suffix)) (def: .public (if test then! else!) (-> Expression Statement Statement Statement) (<| :abstraction ..block (format "if " (:representation test) (..nested (:representation then!)) text.new_line "else" (..nested (:representation else!))))) (template [ ] [(def: .public ( test then!) (-> Expression Statement Statement) (<| :abstraction ..block (format " " (:representation test) (..nested (:representation then!)))))] [when "if"] [while "while"] ) (def: .public (for_in var array iteration!) (-> LVar Expression Statement Statement) (<| :abstraction ..block (format "for " (:representation var) " in " (:representation array) " do " (..nested (:representation iteration!))))) (type: .public Rescue {#classes (List Text) #exception LVar #rescue Statement}) (def: .public (begin body! rescues) (-> Statement (List Rescue) Statement) (<| :abstraction ..block (format "begin" (..nested (:representation body!)) (|> rescues (list\map (.function (_ [classes exception rescue]) (format text.new_line "rescue " (text.join_with ..input_separator classes) " => " (:representation exception) (..nested (:representation rescue))))) (text.join_with text.new_line))))) (def: .public (catch expectation body!) (-> Expression Statement Statement) (<| :abstraction ..block (format "catch(" (:representation expectation) ") do" (..nested (:representation body!))))) (def: .public (return value) (-> Expression Statement) (:abstraction (format "return " (:representation value) ..statement_suffix))) (def: .public (raise message) (-> Expression Computation) (:abstraction (format "raise " (:representation message)))) (template [ ] [(def: .public Statement (|> (text.suffix ..statement_suffix) :abstraction))] [next "next"] [redo "redo"] [break "break"] ) (def: .public (function name args body!) (-> LVar (List LVar) Statement Statement) (<| :abstraction ..block (format "def " (:representation name) (|> args (list\map (|>> :representation)) (text.join_with ..input_separator) (text.enclosed ["(" ")"])) (..nested (:representation body!))))) (def: .public (lambda name args body!) (-> (Maybe LVar) (List Var) Statement Literal) (let [proc (|> (format (|> args (list\map (|>> :representation)) (text.join_with ..input_separator) (text.enclosed' "|")) (..nested (:representation body!))) (text.enclosed ["{" "}"]) (format "lambda "))] (|> (case name #.None proc (#.Some name) (format (:representation name) " = " proc)) (text.enclosed ["(" ")"]) :abstraction))) (template [ ] [(def: .public ( parameter subject) (-> Expression Expression Computation) (:abstraction (format "(" (:representation subject) " " " " (:representation parameter) ")")))] ["==" =] [ "<" <] ["<=" <=] [ ">" >] [">=" >=] [ "+" +] [ "-" -] [ "*" *] [ "/" /] [ "%" %] ["**" pow] ["||" or] ["&&" and] [ "|" bit_or] [ "&" bit_and] [ "^" bit_xor] ["<<" bit_shl] [">>" bit_shr] ) (template [ ] [(def: .public ( subject) (-> Expression Computation) (:abstraction (format "(" (:representation subject) ")")))] ["!" not] ["-" opposite] ) (def: .public (comment commentary on) (All [brand] (-> Text (Code brand) (Code brand))) (:abstraction (format "# " (..safe commentary) text.new_line (:representation on)))) ) (def: .public (do method args object) (-> Text (List Expression) Expression Computation) (|> object (..the method) (..apply/* args))) (def: .public (cond clauses else!) (-> (List [Expression Statement]) Statement Statement) (list\fold (.function (_ [test then!] next!) (..if test then! next!)) else! (list.reversed clauses))) (syntax: (arity_inputs [arity .nat]) (in (case arity 0 (.list) _ (|> (dec arity) (enum.range n.enum 0) (list\map (|>> %.nat code.local_identifier)))))) (syntax: (arity_types [arity .nat]) (in (list.repeated arity (` ..Expression)))) (template [ +] [(with_expansions [ (template.identifier ["apply/" ]) (arity_inputs ) (arity_types ) (template.spliced +)] (def: .public ( function ) (-> Expression Computation) (..apply/* (.list ) function)) (template [] [(`` (def: .public (~~ (template.identifier [ "/" ])) ( (..local ))))] ))] [1 [["print"] ["require"]]] [2 [["print"]]] [3 [["print"]]] ) (def: .public throw/1 (-> Expression Statement) (|>> (..apply/1 (..local "throw")) ..statement))