(.using [library [lux {"-" Symbol Alias Global global function} ["@" target] ["[0]" meta] [abstract [monad {"+" do}]] [control ["[0]" io] ["[0]" maybe ("[1]#[0]" functor)] ["<>" parser ("[1]#[0]" monad) ["<[0]>" code {"+" Parser}]]] [data ["[0]" product] ["[0]" text ("[1]#[0]" equivalence) ["%" format]] [collection ["[0]" list ("[1]#[0]" monad mix)]]] ["[0]" macro {"+" with_symbols} [syntax {"+" syntax:}] ["[0]" code] ["[0]" template]] [type abstract]]]) (with_expansions [ (for @.js "js constant" @.python "python constant" @.lua "lua constant" @.ruby "ruby constant") (for @.js "js apply" @.python "python apply" @.lua "lua apply" @.ruby "ruby apply") (for @.js "js object new" @.python "python apply" (as_is)) (for @.js "js object do" @.python "python object do" @.lua "lua object do" @.ruby "ruby object do") (for @.js "js object get" @.python "python object get" @.lua "lua object get" @.ruby "ruby object get" (as_is)) (for @.python "python import" @.lua "lua import" @.ruby "ruby import" (as_is)) (for @.js "js function" @.python "python function" @.lua "lua function" (as_is))] (abstract: .public (Object brand) Any) (with_expansions [ (for @.js (as_is [Symbol] [Null] [Undefined]) @.python (as_is [None] [Dict]) @.lua (as_is [Nil] [Table]) @.ruby (as_is [Nil])) ] (template [] [(with_expansions [ (template.symbol [ "'"])] (abstract: Any (type: .public (Object ))))] [Function] )) (with_expansions [ (for @.js (as_is [Number Frac]) @.python (as_is [Integer Int] [Float Frac]) @.lua (as_is [Integer Int] [Float Frac]) @.ruby (as_is [Integer Int] [Float Frac])) ] (template [ ] [(type: .public )] [Boolean Bit] [String Text] )) (type: Alias (Maybe Text)) (def: alias (Parser Alias) (<>.maybe (<>.after (.this! (' "as")) .local_symbol))) (type: Optional (Record [#optional? Bit #mandatory Code])) (def: optional (Parser Optional) (let [token "?"] (<| (<>.and (<>.parses? (.text! token))) (<>.after (<>.not (.text! token))) .any))) (type: (Named a) (Record [#name Text #alias Alias #anonymous a])) (template [ ] [(def: (All (_ a) (-> (Parser a) (Parser (Named a)))) (|>> ($_ <>.and ..alias )))] [named .local_symbol] [anonymous (<>#in "")] ) (type: Output Optional) (def: output (Parser Output) ..optional) (type: Global (Named Output)) (def: variables (Parser (List Text)) (<>.else (list) (.tuple (<>.some .local_symbol)))) (def: (generalized $ it) (All (_ a) (-> (-> (List Text) a a) (-> (Parser a) (Parser a)))) (do <>.monad [variables ..variables it it] (in ($ variables it)))) (type: Input (Record [#variables (List Text) #parameters (List Optional) #io? Bit #try? Bit])) (def: input (Parser Input) ($_ <>.and (<>#in (list)) (.tuple (<>.some ..optional)) (<>.parses? (.text! "io")) (<>.parses? (.text! "try")))) (type: Constructor (Named Input)) (def: constructor (Parser Constructor) (<| .form (..generalized (has [#anonymous #variables])) (<>.after (.this! (' new))) (..anonymous ..input))) (type: (Member a) (Record [#static? Bit #member a])) (def: static! (Parser Any) (.text! "static")) (def: (member it) (All (_ a) (-> (Parser a) (Parser (Member a)))) (do [! <>.monad] [static? (<>.parses? ..static!)] (# ! each (|>> [#static? static? #member]) it))) (type: Field (Member (Named Output))) (def: field (Parser Field) (<| .form ..member ..named ..output)) (type: Procedure (Record [#input Input #output Optional])) (def: procedure (Parser (Named Procedure)) (<| (..generalized (has [#anonymous #input #variables])) ..named ($_ <>.and ..input ..optional ))) (type: Method (Member (Named Procedure))) (def: method (Parser Method) (<| .form ..member ..procedure)) (`` (`` (type: Sub (Variant (~~ (for @.lua (~~ (as_is)) @.ruby (~~ (as_is)) {#Constructor Constructor})) {#Field Field} {#Method Method})))) (`` (`` (def: sub (Parser Sub) ($_ <>.or (~~ (for @.lua (~~ (as_is)) @.ruby (~~ (as_is)) ..constructor)) ..field ..method )))) (def: parameters (-> (List Optional) (List Optional)) (|>> list.enumeration (list#each (.function (_ [idx [optional? type]]) [#optional? optional? #mandatory (|> idx %.nat code.local_symbol)])))) (def: (output_type it) (-> Optional Code) (if (the #optional? it) (` (.Maybe (~ (the #mandatory it)))) (the #mandatory it))) (`` (template [ ] [(def: .public ( _) (-> Any Nothing) (:expected ())) (def: .public (-> Any Bit) (|>> )) (template.with_locals [g!it] (as_is (def: g!it' (' g!it)) (def: (host_optional it) (-> Optional Code) (.if (.the #optional? it) (` (.case (~ (the #mandatory it)) {.#Some (~ g!it')} (~ g!it') {.#None} ())) (the #mandatory it))) (def: (lux_optional it output) (-> Optional Code Code) (` (.let [(~ g!it') (~ output)] (~ (if (the #optional? it) (` (.if ( (~ g!it')) {.#None} {.#Some (~ g!it')})) (` (.if (.not ( (~ g!it'))) (~ g!it') (.panic! "Invalid output."))))))))))] (~~ (for @.js [null "js object null" null? "js object null?"] @.python [none "python object none" none? "python object none?"] @.lua [nil "lua object nil" nil? "lua object nil?"] @.ruby [nil "ruby object nil" nil? "ruby object nil?"])) )) (type: Declaration [Text (List Text)]) (type: Namespace Text) (type: Class (Record [#declaration Declaration #class_alias Alias #namespace Namespace #members (List Sub)])) (def: class (Parser Class) ($_ <>.and (<>.either (<>.and .local_symbol (<>#in (list))) (.form (<>.and .local_symbol (<>.some .local_symbol)))) ..alias .text (<>.some ..sub))) (type: Import (Variant {#Class Class} {#Procedure (Named Procedure)} {#Global Global})) (def: import (Parser Import) ($_ <>.or ..class (.form ..procedure) (.form (..named ..output)))) (def: (input_type input :it:) (-> Input Code Code) (let [:it: (if (the #try? input) (` (.Either .Text (~ :it:))) :it:)] (if (the #io? input) (` ((~! io.IO) (~ :it:))) :it:))) (def: (input_term input term) (-> Input Code Code) (let [term (if (the #try? input) (` (.try (~ term))) term)] (if (the #io? input) (` ((~! io.io) (~ term))) term))) (def: (procedure_definition import! source it) (-> (List Code) Code (Named Procedure) Code) (let [g!it (|> (the #alias it) (maybe.else (the #name it)) code.local_symbol) g!variables (list#each code.local_symbol (the [#anonymous #input #variables] it)) input (the [#anonymous #input] it) :parameters: (the #parameters input) g!parameters (..parameters :parameters:) :output: (the [#anonymous #output] it) :input:/* (case :parameters: {.#End} (list (` [])) parameters (list#each ..output_type :parameters:))] (` (.def: ((~ g!it) (~+ (case g!parameters {.#End} (list g!it) _ (list#each (the #mandatory) g!parameters)))) (.All ((~ g!it) (~+ g!variables)) (-> (~+ :input:/*) (~ (|> :output: ..output_type (..input_type input))))) (.exec (~+ import!) (.:expected (~ (<| (..input_term input) (..lux_optional :output:) (` ( (.:expected (~ source)) [(~+ (list#each ..host_optional g!parameters))])))))))))) (def: (namespaced namespace class alias member) (-> Namespace Text Alias Text Text) (|> namespace (text.replaced "[1]" (maybe.else class alias)) (text.replaced "[0]" member))) (def: class_separator ".") (def: host_path (text.replaced .module_separator ..class_separator)) (for @.js (as_is) (def: (imported class) (-> Text Code) (case (text.all_split_by .module_separator class) {.#Item head tail} (list#mix (.function (_ sub super) (` ( (~ (code.text sub)) (.:as (..Object .Any) (~ super))))) (` ( (~ (code.text head)))) tail) {.#End} (` ( (~ (code.text class))))))) (def: (global_definition import! it) (-> (List Code) Global Code) (let [g!name (|> (the #alias it) (maybe.else (the #name it)) code.local_symbol) :output: (the #anonymous it)] (` (.def: (~ g!name) (~ (..output_type :output:)) (.exec (~+ import!) (.:expected (~ (<| (lux_optional :output:) (` ( (~ (code.text (..host_path (the #name it)))))))))))))) (for @.lua (as_is) @.ruby (as_is) (def: (constructor_definition [class_name class_parameters] alias namespace it) (-> Declaration Alias Namespace Constructor Code) (let [g!it (|> it (the #alias) (maybe.else "new") (..namespaced namespace class_name alias) code.local_symbol) input (the #anonymous it) g!input_variables (list#each code.local_symbol (the #variables input)) :parameters: (the #parameters input) g!parameters (..parameters :parameters:) g!class_variables (list#each code.local_symbol class_parameters) g!class (` ((~ (code.local_symbol (maybe.else class_name alias))) (~+ g!class_variables))) :output: [#optional? false #mandatory g!class]] (` (.def: ((~ g!it) (~+ (case g!parameters {.#End} (list g!it) _ (list#each (the #mandatory) g!parameters)))) (.All ((~ g!it) (~+ g!class_variables) (~+ g!input_variables)) (.-> (~+ (list#each ..output_type :parameters:)) (~ (|> :output: ..output_type (..input_type input))))) (.:expected (~ (<| (..input_term input) (..lux_optional :output:) (` ( (~ (for @.js (` ( (~ (code.text (..host_path class_name))))) @.python (` (.:as ..Function (~ (..imported class_name)))))) [(~+ (list#each ..host_optional g!parameters))])))))))))) (def: (static_field_definition import! [class_name class_parameters] alias namespace it) (-> (List Code) Declaration Alias Namespace (Named Output) Code) (let [field (the #name it) g!it (|> (the #alias it) (maybe.else field) (..namespaced namespace class_name alias) code.local_symbol) :field: (the #anonymous it)] (` ((~! syntax:) ((~ g!it) []) (.# (~! meta.monad) (~' in) (.list (`' (.exec (~+ import!) (.:as (~ (..output_type :field:)) (~ (<| (lux_optional :field:) (for @.js (` ( (~ (code.text (%.format (..host_path class_name) "." field))))) @.ruby (` ( (~ (code.text (%.format (..host_path class_name) "::" field))))) (` ( (~ (code.text field)) (~ (..imported class_name)))))))))))))))) (def: (virtual_field_definition [class_name class_parameters] alias namespace it) (-> Declaration Alias Namespace (Named Output) Code) (let [name (the #name it) g!it (|> (the #alias it) (maybe.else name) (..namespaced namespace class_name alias) code.local_symbol) path (%.format (..host_path class_name) "." name) :field: (the #anonymous it) g!variables (list#each code.local_symbol class_parameters) g!class (` ((~ (code.local_symbol (maybe.else class_name alias))) (~+ g!variables)))] (` (.def: ((~ g!it) (~ g!it)) (.All ((~ g!it) (~+ g!variables)) (.-> (~ g!class) (~ (..output_type :field:)))) (.:expected (~ (<| (lux_optional :field:) (` ( (~ (code.text name)) (~ g!it)))))))))) (def: (field_definition import! class alias namespace it) (-> (List Code) Declaration Alias Namespace Field Code) (if (the #static? it) (..static_field_definition import! class alias namespace (the #member it)) (..virtual_field_definition class alias namespace (the #member it)))) (def: (static_method_definition import! [class_name class_parameters] alias namespace it) (-> (List Code) Declaration Alias Namespace (Named Procedure) Code) (let [method (the #name it) name (|> (the #alias it) (maybe.else (the #name it)) (..namespaced namespace class_name alias))] (|> it (has #alias {.#Some name}) (..procedure_definition import! (for @.js (` ( (~ (code.text (%.format (..host_path class_name) "." method))))) @.ruby (` ( (~ (code.text (%.format (..host_path class_name) "::" method))))) (` ( (~ (code.text method)) (.:as (..Object .Any) (~ (..imported class_name)))))))))) (def: (virtual_method_definition [class_name class_parameters] alias namespace it) (-> Declaration Alias Namespace (Named Procedure) Code) (let [method (the #name it) g!it (|> (the #alias it) (maybe.else method) (..namespaced namespace class_name alias) code.local_symbol) procedure (the #anonymous it) input (the #input procedure) g!input_variables (list#each code.local_symbol (the #variables input)) :parameters: (the #parameters input) g!parameters (..parameters :parameters:) g!class_variables (list#each code.local_symbol class_parameters) g!class (` ((~ (code.local_symbol (maybe.else class_name alias))) (~+ g!class_variables))) :output: (the #output procedure)] (` (.def: ((~ g!it) (~+ (list#each (the #mandatory) g!parameters)) (~ g!it)) (.All ((~ g!it) (~+ g!class_variables) (~+ g!input_variables)) (.-> (~+ (list#each ..output_type :parameters:)) (~ g!class) (~ (|> :output: ..output_type (..input_type input))))) (.:expected (~ (<| (..input_term input) (..lux_optional :output:) (` ( (~ (code.text method)) (~ g!it) [(~+ (list#each ..host_optional g!parameters))]))))))))) (def: (method_definition import! class alias namespace it) (-> (List Code) Declaration Alias Namespace Method Code) (if (the #static? it) (static_method_definition import! class alias namespace (the #member it)) (virtual_method_definition class alias namespace (the #member it)))) (syntax: .public (import: [host_module (<>.maybe .text) it ..import]) (let [host_module_import! (: (List Code) (case host_module {.#Some host_module} (list (` ( (~ (code.text host_module))))) {.#None} (list)))] (case it {#Global it} (in (list (..global_definition host_module_import! it))) {#Procedure it} (in (list (..procedure_definition host_module_import! (` ( (~ (code.text (..host_path (the #name it)))))) it))) {#Class it} (let [class (the #declaration it) alias (the #class_alias it) [class_name class_parameters] class namespace (the #namespace it) g!class_variables (list#each code.local_symbol class_parameters) declaration (` ((~ (code.local_symbol (maybe.else class_name alias))) (~+ g!class_variables)))] (in (list& (` (.type: (~ declaration) (..Object (.Primitive (~ (code.text (..host_path class_name))) [(~+ g!class_variables)])))) (list#each (.function (_ member) (`` (`` (case member (~~ (for @.lua (~~ (as_is)) @.ruby (~~ (as_is)) (~~ (as_is {#Constructor it} (..constructor_definition class alias namespace it))))) {#Field it} (..field_definition host_module_import! class alias namespace it) {#Method it} (..method_definition host_module_import! class alias namespace it))))) (the #members it))))) ))) (for @.ruby (as_is) (syntax: .public (function [[self inputs] (.form ($_ <>.and .local_symbol (.tuple (<>.some (<>.and .any .any))))) type .any term .any]) (in (list (` (.<| (.:as ..Function) ( (~ (code.nat (list.size inputs)))) (.:as (.-> [(~+ (list.repeated (list.size inputs) (` .Any)))] .Any)) (.: (.-> [(~+ (list#each product.right inputs))] (~ type))) (.function ((~ (code.local_symbol self)) [(~+ (list#each product.left inputs))]) (~ term)))))))) (for @.js (as_is (template: .public (type_of object) [("js type-of" object)]) (syntax: .public (global [type .any [head tail] (.tuple (<>.and .local_symbol (<>.some .local_symbol)))]) (with_symbols [g!_] (let [global (` ("js constant" (~ (code.text head))))] (case tail {.#End} (in (list (` (: (.Maybe (~ type)) (case (..type_of (~ global)) "undefined" {.#None} (~ g!_) {.#Some (:as (~ type) (~ global))}))))) {.#Item [next tail]} (let [separator "."] (in (list (` (: (.Maybe (~ type)) (case (..type_of (~ global)) "undefined" {.#None} (~ g!_) (..global (~ type) [(~ (code.local_symbol (%.format head "." next))) (~+ (list#each code.local_symbol tail))]))))))))))) (template: (!defined? ) [(.case (..global Any ) {.#None} .false {.#Some _} .true)]) (template [ ] [(def: .public Bit (!defined? ))] [on_browser? [window]] [on_nashorn? [java lang Object]] ) (def: .public on_node_js? Bit (|> (..global (Object Any) [process]) (maybe#each (|>> [] ("js apply" ("js constant" "Object.prototype.toString.call")) (:as Text) (text#= "[object process]"))) (maybe.else false))) ) (as_is)) )