diff options
Diffstat (limited to '')
232 files changed, 5748 insertions, 5710 deletions
diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux index aa5e5c476..7a80d68e7 100644 --- a/stdlib/source/library/lux.lux +++ b/stdlib/source/library/lux.lux @@ -1365,10 +1365,10 @@ ... (type: (Monad m) ... (Interface -... (: (All (_ a) (-> a (m a))) -... #in) -... (: (All (_ a b) (-> (-> a (m b)) (m a) (m b))) -... #then))) +... (is (All (_ a) (-> a (m a))) +... #in) +... (is (All (_ a b) (-> (-> a (m b)) (m a) (m b))) +... #then))) ("lux def type tagged" Monad {#Named [..prelude_module "Monad"] (All (_ !) @@ -2261,7 +2261,7 @@ {#End}}}}}] (` ("lux in-module" (~ (text$ module)) (~ (normal_type type')))) - [_ {#Form {#Item [_ {#Symbol ["" ":~"]}] {#Item expression {#End}}}}] + [_ {#Form {#Item [_ {#Symbol ["" "~"]}] {#Item expression {#End}}}}] expression [_0 {#Form {#Item [_1 {#Variant {#Item binding {#Item body {#End}}}}] @@ -2311,7 +2311,7 @@ (failure "Wrong syntax for type")} tokens)) -(macro:' .public (: tokens) +(macro:' .public (is tokens) ({{#Item type {#Item value {#End}}} (meta#in (list (` ("lux type check" (..type (~ type)) @@ -2321,14 +2321,14 @@ (failure "Wrong syntax for :")} tokens)) -(macro:' .public (:as tokens) +(macro:' .public (as tokens) ({{#Item type {#Item value {#End}}} (meta#in (list (` ("lux type as" (..type (~ type)) (~ value))))) _ - (failure "Wrong syntax for :as")} + (failure "Wrong syntax for as")} tokens)) (def:''' .private (empty? xs) @@ -2377,22 +2377,22 @@ (list#reversed tokens))) (macro:' .private (def:' tokens) - (let' [parts (: (Maybe [Code Code (List Code) (Maybe Code) Code]) - ({{#Item export_policy {#Item [_ {#Form {#Item name args}}] {#Item type {#Item body {#End}}}}} - {#Some [export_policy name args {#Some type} body]} - - {#Item export_policy {#Item name {#Item type {#Item body {#End}}}}} - {#Some [export_policy name {#End} {#Some type} body]} - - {#Item export_policy {#Item [_ {#Form {#Item name args}}] {#Item body {#End}}}} - {#Some [export_policy name args {#None} body]} - - {#Item export_policy {#Item name {#Item body {#End}}}} - {#Some [export_policy name {#End} {#None} body]} - - _ - {#None}} - tokens))] + (let' [parts (is (Maybe [Code Code (List Code) (Maybe Code) Code]) + ({{#Item export_policy {#Item [_ {#Form {#Item name args}}] {#Item type {#Item body {#End}}}}} + {#Some [export_policy name args {#Some type} body]} + + {#Item export_policy {#Item name {#Item type {#Item body {#End}}}}} + {#Some [export_policy name {#End} {#Some type} body]} + + {#Item export_policy {#Item [_ {#Form {#Item name args}}] {#Item body {#End}}}} + {#Some [export_policy name args {#None} body]} + + {#Item export_policy {#Item name {#Item body {#End}}}} + {#Some [export_policy name {#End} {#None} body]} + + _ + {#None}} + tokens))] ({{#Some [export_policy name args ?type body]} (let' [body' ({{#End} body @@ -2401,7 +2401,7 @@ (` (function' (~ name) [(~+ args)] (~ body)))} args) body'' ({{#Some type} - (` (: (~ type) (~ body'))) + (` (is (~ type) (~ body'))) {#None} body'} @@ -2503,12 +2503,12 @@ {#Some bindings} (|> bindings list#reversed - (list#mix (: (-> [Code Code] Code Code) - (function' [lr body'] - (let' [[l r] lr] - (if (symbol? l) - (` ({(~ l) (~ body')} (~ r))) - (` (case (~ r) (~ l) (~ body'))))))) + (list#mix (is (-> [Code Code] Code Code) + (function' [lr body'] + (let' [[l r] lr] + (if (symbol? l) + (` ({(~ l) (~ body')} (~ r))) + (` (case (~ r) (~ l) (~ body'))))))) body) list meta#in) @@ -2520,22 +2520,22 @@ (failure "Wrong syntax for let"))) (macro:' .public (function tokens) - (case (: (Maybe [Text Code (List Code) Code]) - (case tokens - (pattern (list [_ {#Form (list& [_ {#Symbol ["" name]}] head tail)}] body)) - {#Some name head tail body} - - _ - {#None})) + (case (is (Maybe [Text Code (List Code) Code]) + (case tokens + (pattern (list [_ {#Form (list& [_ {#Symbol ["" name]}] head tail)}] body)) + {#Some name head tail body} + + _ + {#None})) {#Some g!name head tail body} (let [g!blank (local_symbol$ "") - nest (: (-> Code (-> Code Code Code)) - (function' [g!name] - (function' [arg body'] - (if (symbol? arg) - (` ([(~ g!name) (~ arg)] (~ body'))) - (` ([(~ g!name) (~ g!blank)] - (.case (~ g!blank) (~ arg) (~ body'))))))))] + nest (is (-> Code (-> Code Code Code)) + (function' [g!name] + (function' [arg body'] + (if (symbol? arg) + (` ([(~ g!name) (~ arg)] (~ body'))) + (` ([(~ g!name) (~ g!blank)] + (.case (~ g!blank) (~ arg) (~ body'))))))))] (meta#in (list (nest (..local_symbol$ g!name) head (list#mix (nest g!blank) body (list#reversed tail)))))) @@ -2750,8 +2750,8 @@ (~ body)))) body (case ?type {#Some type} - (` (: (~ type) - (~ body))) + (` (is (~ type) + (~ body))) {#None} body)] @@ -2809,8 +2809,8 @@ [(macro: .public (<name> tokens) (case (list#reversed tokens) (pattern (list& last init)) - (meta#in (list (list#mix (: (-> Code Code Code) - (function (_ pre post) (` <form>))) + (meta#in (list (list#mix (is (-> Code Code Code) + (function (_ pre post) (` <form>))) last init))) @@ -2831,7 +2831,7 @@ (macro: (maybe#else tokens state) (case tokens (pattern (list else maybe)) - (let [g!temp (: Code [dummy_location {#Symbol ["" ""]}]) + (let [g!temp (is Code [dummy_location {#Symbol ["" ""]}]) code (` (case (~ maybe) {.#Some (~ g!temp)} (~ g!temp) @@ -3125,34 +3125,34 @@ [tokens' (monad#each meta_monad expansion tokens) struct_type ..expected_type tags+type (record_slots struct_type) - tags (: (Meta (List Symbol)) - (case tags+type - {#Some [tags _]} - (meta#in tags) + tags (is (Meta (List Symbol)) + (case tags+type + {#Some [tags _]} + (meta#in tags) - _ - (failure ($_ text#composite - "No tags available for type: " - (type#encoded struct_type))))) - .let [tag_mappings (: (List [Text Code]) - (list#each (function (_ tag) - [(product#right tag) - (symbol$ tag)]) - tags))] + _ + (failure ($_ text#composite + "No tags available for type: " + (type#encoded struct_type))))) + .let [tag_mappings (is (List [Text Code]) + (list#each (function (_ tag) + [(product#right tag) + (symbol$ tag)]) + tags))] members (monad#each meta_monad - (: (-> Code (Meta (List Code))) - (function (_ token) - (case token - (pattern [_ {#Form (list [_ {#Text "lux def"}] [_ {#Symbol ["" slot_name]}] value export_policy)}]) - (case (plist#value slot_name tag_mappings) - {#Some tag} - (in (list tag value)) + (is (-> Code (Meta (List Code))) + (function (_ token) + (case token + (pattern [_ {#Form (list [_ {#Text "lux def"}] [_ {#Symbol ["" slot_name]}] value export_policy)}]) + (case (plist#value slot_name tag_mappings) + {#Some tag} + (in (list tag value)) - _ - (failure (text#composite "Unknown implementation member: " slot_name))) + _ + (failure (text#composite "Unknown implementation member: " slot_name))) - _ - (failure "Invalid implementation member.")))) + _ + (failure "Invalid implementation member.")))) (list#conjoint tokens'))] (in (list (tuple$ (list#conjoint members)))))) @@ -3336,14 +3336,14 @@ module_name current_module_name .let' [type_name (local_symbol$ name) [type labels??] type+labels?? - type' (: (Maybe Code) - (case args - {#End} - {#Some type} + type' (is (Maybe Code) + (case args + {#End} + {#Some type} - _ - {#Some (` (.All ((~ type_name) (~+ (list#each local_symbol$ args))) - (~ type)))}))]] + _ + {#Some (` (.All ((~ type_name) (~+ (list#each local_symbol$ args))) + (~ type)))}))]] (case type' {#Some type''} (let [typeC (` {.#Named [(~ (text$ module_name)) @@ -3398,14 +3398,14 @@ (def: (referral_references defs) (-> (List Code) (Meta (List Text))) (monad#each meta_monad - (: (-> Code (Meta Text)) - (function (_ def) - (case def - [_ {#Symbol ["" name]}] - (meta#in name) + (is (-> Code (Meta Text)) + (function (_ def) + (case def + [_ {#Symbol ["" name]}] + (meta#in name) - _ - (failure "only/+ and exclude/- require symbols.")))) + _ + (failure "only/+ and exclude/- require symbols.")))) defs)) (def: (referrals_parser tokens) @@ -3474,14 +3474,14 @@ (def: (replaced pattern replacement template) (-> Text Text Text Text) - ((: (-> Text Text Text) - (function (again left right) - (case (..text#split_by pattern right) - {#Some [pre post]} - (again ($_ "lux text concat" left pre replacement) post) + ((is (-> Text Text Text) + (function (again left right) + (case (..text#split_by pattern right) + {#Some [pre post]} + (again ($_ "lux text concat" left pre replacement) post) - {#None} - ("lux text concat" left right)))) + {#None} + ("lux text concat" left right)))) "" template)) (def: (alias_stand_in index) @@ -3576,75 +3576,75 @@ (-> Bit Text (List Text) (List Code) (Meta (List Importation))) (do meta_monad [imports' (monad#each meta_monad - (: (-> Code (Meta (List Importation))) - (function (_ token) - (case token - ... Simple - [_ {#Symbol ["" module_name]}] - (do meta_monad - [absolute_module_name (..absolute_module_name nested? relative_root module_name)] - (in (list [#import_name absolute_module_name - #import_alias {#None} - #import_refer [#refer_defs {#All} - #refer_open (list)]]))) - - ... Nested - (pattern [_ {#Tuple (list& [_ {#Symbol ["" module_name]}] extra)}]) - (do meta_monad - [absolute_module_name (case (normal_parallel_path relative_root module_name) - {#Some parallel_path} - (in parallel_path) - - {#None} - (..absolute_module_name nested? relative_root module_name)) - referral+extra (referrals_parser extra) - .let [[referral extra] referral+extra] - openings+extra (openings_parser extra) - .let [[openings extra] openings+extra] - sub_imports (imports_parser #1 absolute_module_name context extra)] - (in (case [referral openings] - [{#Nothing} {#End}] - sub_imports - - _ - (list& [#import_name absolute_module_name - #import_alias {#None} - #import_refer [#refer_defs referral - #refer_open openings]] - sub_imports)))) - - (pattern [_ {#Tuple (list& [_ {#Text alias}] [_ {#Symbol ["" module_name]}] extra)}]) - (do meta_monad - [absolute_module_name (case (normal_parallel_path relative_root module_name) - {#Some parallel_path} - (in parallel_path) - - {#None} - (..absolute_module_name nested? relative_root module_name)) - referral+extra (referrals_parser extra) - .let [[referral extra] referral+extra] - openings+extra (openings_parser extra) - .let [[openings extra] openings+extra - module_alias (..module_alias {#Item module_name context} alias)] - sub_imports (imports_parser #1 absolute_module_name {#Item module_alias context} extra)] - (in (case [referral openings] - [{#Ignore} {#End}] - sub_imports - - _ - (list& [#import_name absolute_module_name - #import_alias {#Some module_alias} - #import_refer [#refer_defs referral - #refer_open openings]] - sub_imports)))) - - ... Unrecognized syntax. - _ - (do meta_monad - [current_module current_module_name] - (failure ($_ text#composite - "Wrong syntax for import @ " current_module - \n (code#encoded token))))))) + (is (-> Code (Meta (List Importation))) + (function (_ token) + (case token + ... Simple + [_ {#Symbol ["" module_name]}] + (do meta_monad + [absolute_module_name (..absolute_module_name nested? relative_root module_name)] + (in (list [#import_name absolute_module_name + #import_alias {#None} + #import_refer [#refer_defs {#All} + #refer_open (list)]]))) + + ... Nested + (pattern [_ {#Tuple (list& [_ {#Symbol ["" module_name]}] extra)}]) + (do meta_monad + [absolute_module_name (case (normal_parallel_path relative_root module_name) + {#Some parallel_path} + (in parallel_path) + + {#None} + (..absolute_module_name nested? relative_root module_name)) + referral+extra (referrals_parser extra) + .let [[referral extra] referral+extra] + openings+extra (openings_parser extra) + .let [[openings extra] openings+extra] + sub_imports (imports_parser #1 absolute_module_name context extra)] + (in (case [referral openings] + [{#Nothing} {#End}] + sub_imports + + _ + (list& [#import_name absolute_module_name + #import_alias {#None} + #import_refer [#refer_defs referral + #refer_open openings]] + sub_imports)))) + + (pattern [_ {#Tuple (list& [_ {#Text alias}] [_ {#Symbol ["" module_name]}] extra)}]) + (do meta_monad + [absolute_module_name (case (normal_parallel_path relative_root module_name) + {#Some parallel_path} + (in parallel_path) + + {#None} + (..absolute_module_name nested? relative_root module_name)) + referral+extra (referrals_parser extra) + .let [[referral extra] referral+extra] + openings+extra (openings_parser extra) + .let [[openings extra] openings+extra + module_alias (..module_alias {#Item module_name context} alias)] + sub_imports (imports_parser #1 absolute_module_name {#Item module_alias context} extra)] + (in (case [referral openings] + [{#Ignore} {#End}] + sub_imports + + _ + (list& [#import_name absolute_module_name + #import_alias {#Some module_alias} + #import_refer [#refer_defs referral + #refer_open openings]] + sub_imports)))) + + ... Unrecognized syntax. + _ + (do meta_monad + [current_module current_module_name] + (failure ($_ text#composite + "Wrong syntax for import @ " current_module + \n (code#encoded token))))))) imports)] (in (list#conjoint imports')))) @@ -3658,28 +3658,28 @@ [current_module modules])] (case (plist#value module modules) {#Some =module} - (let [to_alias (list#each (: (-> [Text Global] - (List Text)) - (function (_ [name definition]) - (case definition - {#Alias _} - (list) - - {#Definition [exported? def_type def_value]} - (if exported? - (list name) - (list)) - - {#Type [exported? type labels]} - (if exported? - (list name) - (list)) - - {#Tag _} - (list) - - {#Slot _} - (list)))) + (let [to_alias (list#each (is (-> [Text Global] + (List Text)) + (function (_ [name definition]) + (case definition + {#Alias _} + (list) + + {#Definition [exported? def_type def_value]} + (if exported? + (list name) + (list)) + + {#Type [exported? type labels]} + (if exported? + (list name) + (list)) + + {#Tag _} + (list) + + {#Slot _} + (list)))) (let [[..#module_hash _ ..#module_aliases _ ..#definitions definitions ..#imports _ ..#module_state _] =module] definitions))] {#Right state (list#conjoint to_alias)}) @@ -3728,19 +3728,19 @@ ..#scopes scopes ..#type_context types ..#host host ..#seed seed ..#expected expected ..#location location ..#extensions extensions ..#scope_type_vars scope_type_vars ..#eval _eval] - (list#one (: (-> Scope (Maybe Type)) - (function (_ env) - (case env - [..#name _ - ..#inner _ - ..#locals [..#counter _ ..#mappings locals] - ..#captured _] - (list#one (: (-> [Text [Type Any]] (Maybe Type)) - (function (_ [bname [type _]]) - (if (text#= name bname) - {#Some type} - {#None}))) - locals)))) + (list#one (is (-> Scope (Maybe Type)) + (function (_ env) + (case env + [..#name _ + ..#inner _ + ..#locals [..#counter _ ..#mappings locals] + ..#captured _] + (list#one (is (-> [Text [Type Any]] (Maybe Type)) + (function (_ [bname [type _]]) + (if (text#= name bname) + {#Some type} + {#None}))) + locals)))) scopes))) (def: (definition_type name state) @@ -3834,25 +3834,25 @@ [.let [[module name] full_name] current_module current_module_name] (function (_ compiler) - (let [temp (: (Either Text [Lux Type]) - (if (text#= "" module) - (case (in_env name compiler) - {#Some struct_type} - {#Right [compiler struct_type]} + (let [temp (is (Either Text [Lux Type]) + (if (text#= "" module) + (case (in_env name compiler) + {#Some struct_type} + {#Right [compiler struct_type]} - _ - (case (definition_type [current_module name] compiler) - {#Some struct_type} - {#Right [compiler struct_type]} + _ + (case (definition_type [current_module name] compiler) + {#Some struct_type} + {#Right [compiler struct_type]} - _ - {#Left ($_ text#composite "Unknown var: " (symbol#encoded full_name))})) - (case (definition_type full_name compiler) - {#Some struct_type} - {#Right [compiler struct_type]} + _ + {#Left ($_ text#composite "Unknown var: " (symbol#encoded full_name))})) + (case (definition_type full_name compiler) + {#Some struct_type} + {#Right [compiler struct_type]} - _ - {#Left ($_ text#composite "Unknown var: " (symbol#encoded full_name))})))] + _ + {#Left ($_ text#composite "Unknown var: " (symbol#encoded full_name))})))] (case temp {#Right [compiler {#Var type_id}]} (let [[..#info _ ..#source _ ..#current_module _ ..#modules _ @@ -3903,39 +3903,39 @@ {#Some tags&members} (do meta_monad - [full_body ((: (-> Symbol [(List Symbol) (List Type)] Code (Meta Code)) - (function (again source [tags members] target) - (let [locals (list#each (function (_ [t_module t_name]) - [[t_module t_name] - ["" (..module_alias (list t_name) alias)]]) - tags) - pattern (case locals - (pattern (list [slot binding])) - (symbol$ binding) - - _ - (|> locals - (list#each (function (_ [slot binding]) - (list (symbol$ slot) - (symbol$ binding)))) - list#conjoint - tuple$))] - (do meta_monad - [enhanced_target (monad#mix meta_monad - (function (_ [[_ m_local] m_type] enhanced_target) - (do meta_monad - [m_implementation (record_slots m_type)] - (case m_implementation - {#Some m_tags&members} - (again m_local - m_tags&members - enhanced_target) - - {#None} - (in enhanced_target)))) - target - (zipped/2 locals members))] - (in (` ({(~ pattern) (~ enhanced_target)} (~ (symbol$ source))))))))) + [full_body ((is (-> Symbol [(List Symbol) (List Type)] Code (Meta Code)) + (function (again source [tags members] target) + (let [locals (list#each (function (_ [t_module t_name]) + [[t_module t_name] + ["" (..module_alias (list t_name) alias)]]) + tags) + pattern (case locals + (pattern (list [slot binding])) + (symbol$ binding) + + _ + (|> locals + (list#each (function (_ [slot binding]) + (list (symbol$ slot) + (symbol$ binding)))) + list#conjoint + tuple$))] + (do meta_monad + [enhanced_target (monad#mix meta_monad + (function (_ [[_ m_local] m_type] enhanced_target) + (do meta_monad + [m_implementation (record_slots m_type)] + (case m_implementation + {#Some m_tags&members} + (again m_local + m_tags&members + enhanced_target) + + {#None} + (in enhanced_target)))) + target + (zipped/2 locals members))] + (in (` ({(~ pattern) (~ enhanced_target)} (~ (symbol$ source))))))))) name tags&members body)] (in (list full_body))))) @@ -3947,10 +3947,10 @@ (pattern (list& else branches')) (case (pairs branches') {#Some branches'} - (meta#in (list (list#mix (: (-> [Code Code] Code Code) - (function (_ branch else) - (let [[then ?] branch] - (` (if (~ ?) (~ then) (~ else)))))) + (meta#in (list (list#mix (is (-> [Code Code] Code Code) + (function (_ branch else) + (let [[then ?] branch] + (` (if (~ ?) (~ then) (~ else)))))) else branches'))) @@ -3987,12 +3987,12 @@ (case (interface_methods type) {#Some members} (let [pattern (|> (zipped/2 tags (enumeration members)) - (list#each (: (-> [Symbol [Nat Type]] (List Code)) - (function (_ [[r_module r_name] [r_idx r_type]]) - (list (symbol$ [r_module r_name]) - (if ("lux i64 =" idx r_idx) - g!output - g!_))))) + (list#each (is (-> [Symbol [Nat Type]] (List Code)) + (function (_ [[r_module r_name] [r_idx r_type]]) + (list (symbol$ [r_module r_name]) + (if ("lux i64 =" idx r_idx) + g!output + g!_))))) list#conjoint tuple$)] (meta#in (list (` ({(~ pattern) (~ g!output)} (~ record)))))) @@ -4001,9 +4001,9 @@ (failure "the can only use records."))) (pattern (list [_ {#Tuple slots}] record)) - (meta#in (list (list#mix (: (-> Code Code Code) - (function (_ slot inner) - (` (..the (~ slot) (~ inner))))) + (meta#in (list (list#mix (is (-> Code Code Code) + (function (_ slot inner) + (` (..the (~ slot) (~ inner))))) record slots))) @@ -4034,9 +4034,9 @@ {#Some [tags' members']} (do meta_monad [decls' (monad#each meta_monad - (: (-> [Nat Symbol Type] (Meta (List Code))) - (function (_ [sub_tag_index sname stype]) - (open_declaration alias tags' sub_tag_index sname source+ stype))) + (is (-> [Nat Symbol Type] (Meta (List Code))) + (function (_ [sub_tag_index sname stype]) + (open_declaration alias tags' sub_tag_index sname source+ stype))) (enumeration (zipped/2 tags' members')))] (meta#in (list#conjoint decls'))) @@ -4057,9 +4057,9 @@ (case output {#Some [tags members]} (do meta_monad - [decls' (monad#each meta_monad (: (-> [Nat Symbol Type] (Meta (List Code))) - (function (_ [tag_index sname stype]) - (open_declaration alias tags tag_index sname source stype))) + [decls' (monad#each meta_monad (is (-> [Nat Symbol Type] (Meta (List Code))) + (function (_ [tag_index sname stype]) + (open_declaration alias tags tag_index sname source stype))) (enumeration (zipped/2 tags members)))] (meta#in (list#conjoint decls'))) @@ -4118,15 +4118,15 @@ (-> Text Refer (Meta (List Code))) (do meta_monad [current_module ..current_module_name - .let [test_referrals (: (-> Text (List Text) (List Text) (Meta (List Any))) - (function (_ module_name all_defs referred_defs) - (monad#each meta_monad - (: (-> Text (Meta Any)) - (function (_ _def) - (if (is_member? all_defs _def) - (meta#in []) - (failure ($_ text#composite _def " is not defined in module " module_name " @ " current_module))))) - referred_defs)))] + .let [test_referrals (is (-> Text (List Text) (List Text) (Meta (List Any))) + (function (_ module_name all_defs referred_defs) + (monad#each meta_monad + (is (-> Text (Meta Any)) + (function (_ _def) + (if (is_member? all_defs _def) + (meta#in []) + (failure ($_ text#composite _def " is not defined in module " module_name " @ " current_module))))) + referred_defs)))] defs' (case r_defs {#All} (exported_definitions module_name) @@ -4148,16 +4148,16 @@ {#Nothing} (in (list))) - .let [defs (list#each (: (-> Text Code) - (function (_ def) - (` ("lux def alias" (~ (local_symbol$ def)) (~ (symbol$ [module_name def])))))) + .let [defs (list#each (is (-> Text Code) + (function (_ def) + (` ("lux def alias" (~ (local_symbol$ def)) (~ (symbol$ [module_name def])))))) defs') openings (|> r_opens - (list#each (: (-> Openings (List Code)) - (function (_ [alias structs]) - (list#each (function (_ name) - (` (open: (~ (text$ alias)) (~ (symbol$ [module_name name]))))) - structs)))) + (list#each (is (-> Openings (List Code)) + (function (_ [alias structs]) + (list#each (function (_ name) + (` (open: (~ (text$ alias)) (~ (symbol$ [module_name name]))))) + structs)))) list#conjoint)]] (in (list#composite defs openings)))) @@ -4174,22 +4174,22 @@ (def: (refer_code module_name module_alias' [r_defs r_opens]) (-> Text (Maybe Text) Refer Code) (let [module_alias (..maybe#else module_name module_alias') - localizations (: (List Code) - (case r_defs - {#All} - (list (' "*")) - - {#Only defs} - (list (variant$ (list& (' "+") (list#each local_symbol$ defs)))) - - {#Exclude defs} - (list (variant$ (list& (' "-") (list#each local_symbol$ defs)))) - - {#Ignore} - (list) - - {#Nothing} - (list))) + localizations (is (List Code) + (case r_defs + {#All} + (list (' "*")) + + {#Only defs} + (list (variant$ (list& (' "+") (list#each local_symbol$ defs)))) + + {#Exclude defs} + (list (variant$ (list& (' "-") (list#each local_symbol$ defs)))) + + {#Ignore} + (list) + + {#Nothing} + (list))) openings (list#each (function (_ [alias structs]) (form$ (list& (text$ (..module_alias (list (alias_stand_in 0) module_alias) alias)) (list#each local_symbol$ structs)))) @@ -4221,26 +4221,26 @@ {#Some members} (do meta_monad [pattern' (monad#each meta_monad - (: (-> [Symbol [Nat Type]] (Meta [Symbol Nat Code])) - (function (_ [r_slot_name [r_idx r_type]]) - (do meta_monad - [g!slot (..generated_symbol "")] - (meta#in [r_slot_name r_idx g!slot])))) + (is (-> [Symbol [Nat Type]] (Meta [Symbol Nat Code])) + (function (_ [r_slot_name [r_idx r_type]]) + (do meta_monad + [g!slot (..generated_symbol "")] + (meta#in [r_slot_name r_idx g!slot])))) (zipped/2 tags (enumeration members)))] (let [pattern (|> pattern' - (list#each (: (-> [Symbol Nat Code] (List Code)) - (function (_ [r_slot_name r_idx r_var]) - (list (symbol$ r_slot_name) - r_var)))) + (list#each (is (-> [Symbol Nat Code] (List Code)) + (function (_ [r_slot_name r_idx r_var]) + (list (symbol$ r_slot_name) + r_var)))) list#conjoint tuple$) output (|> pattern' - (list#each (: (-> [Symbol Nat Code] (List Code)) - (function (_ [r_slot_name r_idx r_var]) - (list (symbol$ r_slot_name) - (if ("lux i64 =" idx r_idx) - value - r_var))))) + (list#each (is (-> [Symbol Nat Code] (List Code)) + (function (_ [r_slot_name r_idx r_var]) + (list (symbol$ r_slot_name) + (if ("lux i64 =" idx r_idx) + value + r_var))))) list#conjoint tuple$)] (meta#in (list (` ({(~ pattern) (~ output)} (~ record))))))) @@ -4256,20 +4256,20 @@ _ (do meta_monad [bindings (monad#each meta_monad - (: (-> Code (Meta Code)) - (function (_ _) (..generated_symbol "temp"))) + (is (-> Code (Meta Code)) + (function (_ _) (..generated_symbol "temp"))) slots) .let [pairs (zipped/2 slots bindings) - update_expr (list#mix (: (-> [Code Code] Code Code) - (function (_ [s b] v) - (` (..has (~ s) (~ v) (~ b))))) + update_expr (list#mix (is (-> [Code Code] Code Code) + (function (_ [s b] v) + (` (..has (~ s) (~ v) (~ b))))) value (list#reversed pairs)) - [_ accesses'] (list#mix (: (-> [Code Code] [Code (List (List Code))] [Code (List (List Code))]) - (function (_ [new_slot new_binding] [old_record accesses']) - [(` (the (~ new_slot) (~ new_binding))) - {#Item (list new_binding old_record) accesses'}])) - [record (: (List (List Code)) {#End})] + [_ accesses'] (list#mix (is (-> [Code Code] [Code (List (List Code))] [Code (List (List Code))]) + (function (_ [new_slot new_binding] [old_record accesses']) + [(` (the (~ new_slot) (~ new_binding))) + {#Item (list new_binding old_record) accesses'}])) + [record (is (List (List Code)) {#End})] pairs) accesses (list#conjoint (list#reversed accesses'))]] (in (list (` (let [(~+ accesses)] @@ -4304,26 +4304,26 @@ {#Some members} (do meta_monad [pattern' (monad#each meta_monad - (: (-> [Symbol [Nat Type]] (Meta [Symbol Nat Code])) - (function (_ [r_slot_name [r_idx r_type]]) - (do meta_monad - [g!slot (..generated_symbol "")] - (meta#in [r_slot_name r_idx g!slot])))) + (is (-> [Symbol [Nat Type]] (Meta [Symbol Nat Code])) + (function (_ [r_slot_name [r_idx r_type]]) + (do meta_monad + [g!slot (..generated_symbol "")] + (meta#in [r_slot_name r_idx g!slot])))) (zipped/2 tags (enumeration members)))] (let [pattern (|> pattern' - (list#each (: (-> [Symbol Nat Code] (List Code)) - (function (_ [r_slot_name r_idx r_var]) - (list (symbol$ r_slot_name) - r_var)))) + (list#each (is (-> [Symbol Nat Code] (List Code)) + (function (_ [r_slot_name r_idx r_var]) + (list (symbol$ r_slot_name) + r_var)))) list#conjoint tuple$) output (|> pattern' - (list#each (: (-> [Symbol Nat Code] (List Code)) - (function (_ [r_slot_name r_idx r_var]) - (list (symbol$ r_slot_name) - (if ("lux i64 =" idx r_idx) - (` ((~ fun) (~ r_var))) - r_var))))) + (list#each (is (-> [Symbol Nat Code] (List Code)) + (function (_ [r_slot_name r_idx r_var]) + (list (symbol$ r_slot_name) + (if ("lux i64 =" idx r_idx) + (` ((~ fun) (~ r_var))) + r_var))))) list#conjoint tuple$)] (meta#in (list (` ({(~ pattern) (~ output)} (~ record))))))) @@ -4368,20 +4368,20 @@ [_ {#Tuple templates}])}] [_ {#Form data}] branches)) - (case (: (Maybe (List Code)) - (do maybe_monad - [bindings' (monad#each maybe_monad symbol_short bindings) - data' (monad#each maybe_monad tuple_list data)] - (let [num_bindings (list#size bindings')] - (if (every? (|>> ("lux i64 =" num_bindings)) - (list#each list#size data')) - (let [apply (: (-> Replacement_Environment (List Code)) - (function (_ env) (list#each (realized_template env) templates)))] - (|> data' - (list#each (function#composite apply (replacement_environment bindings'))) - list#conjoint - in)) - {#None})))) + (case (is (Maybe (List Code)) + (do maybe_monad + [bindings' (monad#each maybe_monad symbol_short bindings) + data' (monad#each maybe_monad tuple_list data)] + (let [num_bindings (list#size bindings')] + (if (every? (|>> ("lux i64 =" num_bindings)) + (list#each list#size data')) + (let [apply (is (-> Replacement_Environment (List Code)) + (function (_ env) (list#each (realized_template env) templates)))] + (|> data' + (list#each (function#composite apply (replacement_environment bindings'))) + list#conjoint + in)) + {#None})))) {#Some output} (meta#in (list#composite output branches)) @@ -4465,10 +4465,10 @@ inits (list#each product#right pairs)] (if (every? symbol? inits) (do meta_monad - [inits' (: (Meta (List Symbol)) - (case (monad#each maybe_monad symbol_name inits) - {#Some inits'} (meta#in inits') - {#None} (failure "Wrong syntax for loop"))) + [inits' (is (Meta (List Symbol)) + (case (monad#each maybe_monad symbol_name inits) + {#Some inits'} (meta#in inits') + {#None} (failure "Wrong syntax for loop"))) init_types (monad#each meta_monad type_definition inits') expected ..expected_type] (meta#in (list (` (("lux type check" @@ -4479,8 +4479,8 @@ (~+ inits)))))) (do meta_monad [aliases (monad#each meta_monad - (: (-> Code (Meta Code)) - (function (_ _) (..generated_symbol ""))) + (is (-> Code (Meta Code)) + (function (_ _) (..generated_symbol ""))) inits)] (meta#in (list (` (let [(~+ (..interleaved aliases inits))] (.loop (~ name) @@ -4516,14 +4516,14 @@ (case (parsed (andP (tupleP (someP bindingP)) (someP anyP)) tokens) {#Some [bindings bodies]} (loop [bindings bindings - map (: (PList (List Code)) - (list))] - (let [normal (: (-> Code (List Code)) - (function (_ it) - (list#mix (function (_ [binding expansion] it) - (list#conjoint (list#each (with_expansions' binding expansion) it))) - (list it) - map)))] + map (is (PList (List Code)) + (list))] + (let [normal (is (-> Code (List Code)) + (function (_ it) + (list#mix (function (_ [binding expansion] it) + (list#conjoint (list#each (with_expansions' binding expansion) it))) + (list it) + map)))] (case bindings {#Item [var_name expr] &rest} (do meta_monad @@ -4571,7 +4571,7 @@ (case (flat_alias type) (pattern#template [<name> <type> <wrapper>] [{#Named ["library/lux" <name>] _} - (in (<wrapper> (:as <type> value)))]) + (in (<wrapper> (as <type> value)))]) (["Bit" Bit bit$] ["Nat" Nat nat$] ["Int" Int int$] @@ -4658,7 +4658,7 @@ (list) (list g!_ (` {.#None})))))))) (` {.#Some (~ body)}) - (: (List [Code Code]) (list#reversed levels)))] + (is (List [Code Code]) (list#reversed levels)))] (list init_pattern inner_pattern_body))) (macro: (pattern#multi tokens) @@ -4713,7 +4713,7 @@ (-> a a Bit)) ("lux is" reference sample)) -(macro: .public (:expected tokens) +(macro: .public (as_expected tokens) (case tokens (pattern (list expr)) (do meta_monad @@ -4721,7 +4721,7 @@ (in (list (` ("lux type as" (~ (type_code type)) (~ expr)))))) _ - (failure (..wrong_syntax_error (symbol ..:expected))))) + (failure (..wrong_syntax_error (symbol ..as_expected))))) (def: location (Meta Location) @@ -4741,7 +4741,7 @@ _ (failure (..wrong_syntax_error (symbol ..undefined))))) -(macro: .public (:of tokens) +(macro: .public (type_of tokens) (case tokens (pattern (list [_ {#Symbol var_name}])) (do meta_monad @@ -4752,10 +4752,10 @@ (do meta_monad [g!temp (..generated_symbol "g!temp")] (in (list (` (let [(~ g!temp) (~ expression)] - (..:of (~ g!temp))))))) + (..type_of (~ g!temp))))))) _ - (failure (..wrong_syntax_error (symbol ..:of))))) + (failure (..wrong_syntax_error (symbol ..type_of))))) (def: (templateP tokens) (-> (List Code) (Maybe [Code Text (List Text) (List Code)])) @@ -4796,7 +4796,7 @@ (template [<name> <to>] [(template: .public (<name> it) - [(..|> it (..: (..I64 ..Any)) (..:as <to>))])] + [(..|> it (..is (..I64 ..Any)) (..as <to>))])] [i64 ..I64] [nat ..Nat] @@ -4837,7 +4837,7 @@ (case (..flat_alias type) (pattern#or {#Primitive "#Text" {#End}} {#Named ["library/lux" "Text"] {#Primitive "#Text" {#End}}}) - (in (:as ..Text value)) + (in (as ..Text value)) _ (failure ($_ text#composite @@ -4879,7 +4879,7 @@ {.#None} (failure (..wrong_syntax_error (symbol ..for))))) -... TODO: Delete "scope_type_vars" (including the #scope_type_vars Lux state) and ":parameter" ASAP. +... TODO: Delete "scope_type_vars" (including the #scope_type_vars Lux state) and "parameter" ASAP. (for "{old}" (as_is (def: (scope_type_vars state) (Meta (List Nat)) (case state @@ -4889,7 +4889,7 @@ ..#scope_type_vars scope_type_vars ..#eval _eval] {#Right [state scope_type_vars]})) - (macro: .public (:parameter tokens) + (macro: .public (parameter tokens) (case tokens (pattern (list [_ {#Nat idx}])) (do meta_monad @@ -4910,13 +4910,13 @@ [current_module ..current_module_name imports (imports_parser #0 current_module {#End} _imports) .let [=imports (|> imports - (list#each (: (-> Importation Code) - (function (_ [module_name m_alias =refer]) - (` [(~ (text$ module_name)) (~ (text$ (..maybe#else "" m_alias)))])))) + (list#each (is (-> Importation Code) + (function (_ [module_name m_alias =refer]) + (` [(~ (text$ module_name)) (~ (text$ (..maybe#else "" m_alias)))])))) tuple$) - =refers (list#each (: (-> Importation Code) - (function (_ [module_name m_alias =refer]) - (refer_code module_name m_alias =refer))) + =refers (list#each (is (-> Importation Code) + (function (_ [module_name m_alias =refer]) + (refer_code module_name m_alias =refer))) imports) =module (` ("lux def module" (~ =imports)))] g!_ (..generated_symbol "")] @@ -4974,23 +4974,6 @@ Bit #1) -(macro: .public (:let tokens) - (case tokens - (pattern (list [_ {#Tuple bindings}] bodyT)) - (case (..pairs bindings) - {#Some bindings} - (meta#in (list (` (..with_expansions [(~+ (|> bindings - (list#each (function (_ [localT valueT]) - (list localT (` (..as_is (~ valueT)))))) - (list#mix list#composite (list))))] - (~ bodyT))))) - - {#None} - (..failure ":let requires an even number of parts")) - - _ - (..failure (..wrong_syntax_error (symbol ..:let))))) - (macro: .public (try tokens) (case tokens (pattern (list expression)) @@ -5055,4 +5038,4 @@ (def: .public macro (-> Macro Macro') - (|>> (:as Macro'))) + (|>> (as Macro'))) diff --git a/stdlib/source/library/lux/abstract/apply.lux b/stdlib/source/library/lux/abstract/apply.lux index 6a509bb0a..0d3a0fd1e 100644 --- a/stdlib/source/library/lux/abstract/apply.lux +++ b/stdlib/source/library/lux/abstract/apply.lux @@ -8,11 +8,11 @@ (type: .public (Apply f) (Interface - (: (Functor f) - &functor) - (: (All (_ a b) - (-> (f a) (f (-> a b)) (f b))) - on))) + (is (Functor f) + &functor) + (is (All (_ a b) + (-> (f a) (f (-> a b)) (f b))) + on))) (implementation: .public (composite f_monad f_apply g_apply) (All (_ F G) @@ -29,7 +29,7 @@ (for @.old (let [fgf' (# f_apply on fgf (# f_monad in (function (_ gf gx) (# g_apply on gx gf))))] - (:expected (# f_apply on (:expected fgx) (:expected fgf')))) + (as_expected (# f_apply on (as_expected fgx) (as_expected fgf')))) (let [fgf' (# f_apply on fgf (# f_monad in (function (_ gf gx) (# g_apply on gx gf))))] diff --git a/stdlib/source/library/lux/abstract/codec.lux b/stdlib/source/library/lux/abstract/codec.lux index 4e146fa41..d7ff3c13f 100644 --- a/stdlib/source/library/lux/abstract/codec.lux +++ b/stdlib/source/library/lux/abstract/codec.lux @@ -1,18 +1,18 @@ (.using - [library - [lux "*" - [control - ["[0]" try {"+" Try}]]]] - [// - [monad {"+" do}] - ["[0]" functor]]) + [library + [lux "*" + [control + ["[0]" try {"+" Try}]]]] + [// + [monad {"+" do}] + ["[0]" functor]]) (type: .public (Codec m a) (Interface - (: (-> a m) - encoded) - (: (-> m (Try a)) - decoded))) + (is (-> a m) + encoded) + (is (-> m (Try a)) + decoded))) (implementation: .public (composite cb_codec ba_codec) (All (_ a b c) diff --git a/stdlib/source/library/lux/abstract/comonad.lux b/stdlib/source/library/lux/abstract/comonad.lux index b5c1598d2..a0dd97014 100644 --- a/stdlib/source/library/lux/abstract/comonad.lux +++ b/stdlib/source/library/lux/abstract/comonad.lux @@ -14,48 +14,48 @@ (type: .public (CoMonad w) (Interface - (: (Functor w) - &functor) - (: (All (_ a) - (-> (w a) a)) - out) - (: (All (_ a) - (-> (w a) (w (w a)))) - disjoint))) + (is (Functor w) + &functor) + (is (All (_ a) + (-> (w a) a)) + out) + (is (All (_ a) + (-> (w a) (w (w a)))) + disjoint))) (macro: .public (be tokens state) - (case (: (Maybe [(Maybe Text) Code (List Code) Code]) - (case tokens - (pattern (list [_ {.#Tuple (list [_ {.#Symbol ["" name]}] comonad)}] [_ {.#Tuple bindings}] body)) - {.#Some [{.#Some name} comonad bindings body]} - - (pattern (list comonad [_ {.#Tuple bindings}] body)) - {.#Some [{.#None} comonad bindings body]} + (case (is (Maybe [(Maybe Text) Code (List Code) Code]) + (case tokens + (pattern (list [_ {.#Tuple (list [_ {.#Symbol ["" name]}] comonad)}] [_ {.#Tuple bindings}] body)) + {.#Some [{.#Some name} comonad bindings body]} + + (pattern (list comonad [_ {.#Tuple bindings}] body)) + {.#Some [{.#None} comonad bindings body]} - _ - {.#None})) + _ + {.#None})) {.#Some [?name comonad bindings body]} (case (list.pairs bindings) {.#Some bindings} (let [[module short] (symbol ..be) - symbol (: (-> Text Code) - (|>> ($_ "lux text concat" module " " short " ") [""] {.#Symbol} [location.dummy])) + symbol (is (-> Text Code) + (|>> ($_ "lux text concat" module " " short " ") [""] {.#Symbol} [location.dummy])) g!_ (symbol "_") g!each (symbol "each") g!disjoint (symbol "disjoint") - body' (list#mix (: (-> [Code Code] Code Code) - (function (_ binding body') - (with_expansions [<default> (` (|> (~ value) (~ g!disjoint) ((~ g!each) (function ((~ g!_) (~ var)) (~ body')))))] - (let [[var value] binding] - (case var - [_ {.#Symbol ["" _]}] - <default> + body' (list#mix (is (-> [Code Code] Code Code) + (function (_ binding body') + (with_expansions [<default> (` (|> (~ value) (~ g!disjoint) ((~ g!each) (function ((~ g!_) (~ var)) (~ body')))))] + (let [[var value] binding] + (case var + [_ {.#Symbol ["" _]}] + <default> - [_ {.#Symbol _}] - (` ((~ var) (~ value) (~ body'))) + [_ {.#Symbol _}] + (` ((~ var) (~ value) (~ body'))) - _ - <default>))))) + _ + <default>))))) body (list.reversed bindings))] {.#Right [state (list (case ?name diff --git a/stdlib/source/library/lux/abstract/enum.lux b/stdlib/source/library/lux/abstract/enum.lux index c172df2ab..fd9e19e37 100644 --- a/stdlib/source/library/lux/abstract/enum.lux +++ b/stdlib/source/library/lux/abstract/enum.lux @@ -6,16 +6,16 @@ (type: .public (Enum e) (Interface - (: (Order e) &order) - (: (-> e e) succ) - (: (-> e e) pred))) + (is (Order e) &order) + (is (-> e e) succ) + (is (-> e e) pred))) (def: .public (range enum from to) (All (_ a) (-> (Enum a) a a (List a))) (let [(open "/#[0]") enum] (loop [end to - output (`` (: (List (~~ (:of from))) - {.#End}))] + output (`` (is (List (~~ (type_of from))) + {.#End}))] (cond (/#< end from) (again (/#pred end) {.#Item end output}) diff --git a/stdlib/source/library/lux/abstract/equivalence.lux b/stdlib/source/library/lux/abstract/equivalence.lux index 30ed40f20..3a28cbba2 100644 --- a/stdlib/source/library/lux/abstract/equivalence.lux +++ b/stdlib/source/library/lux/abstract/equivalence.lux @@ -1,14 +1,14 @@ (.using - [library - [lux "*"]] - [// - [functor - ["[0]" contravariant]]]) + [library + [lux "*"]] + [// + [functor + ["[0]" contravariant]]]) (type: .public (Equivalence a) (Interface - (: (-> a a Bit) - =))) + (is (-> a a Bit) + =))) (def: .public (rec sub) (All (_ a) diff --git a/stdlib/source/library/lux/abstract/functor.lux b/stdlib/source/library/lux/abstract/functor.lux index 636e4c592..1dd348bc3 100644 --- a/stdlib/source/library/lux/abstract/functor.lux +++ b/stdlib/source/library/lux/abstract/functor.lux @@ -4,10 +4,10 @@ (type: .public (Functor f) (Interface - (: (All (_ a b) - (-> (-> a b) - (-> (f a) (f b)))) - each))) + (is (All (_ a b) + (-> (-> a b) + (-> (f a) (f b)))) + each))) (type: .public (Or f g) (All (_ a) (.Or (f a) (g a)))) diff --git a/stdlib/source/library/lux/abstract/functor/contravariant.lux b/stdlib/source/library/lux/abstract/functor/contravariant.lux index 5366a4ecf..8777299c4 100644 --- a/stdlib/source/library/lux/abstract/functor/contravariant.lux +++ b/stdlib/source/library/lux/abstract/functor/contravariant.lux @@ -1,10 +1,10 @@ (.using - [library - [lux "*"]]) + [library + [lux "*"]]) (type: .public (Functor f) (Interface - (: (All (_ a b) - (-> (-> b a) - (-> (f a) (f b)))) - each))) + (is (All (_ a b) + (-> (-> b a) + (-> (f a) (f b)))) + each))) diff --git a/stdlib/source/library/lux/abstract/hash.lux b/stdlib/source/library/lux/abstract/hash.lux index c556c4598..04610b639 100644 --- a/stdlib/source/library/lux/abstract/hash.lux +++ b/stdlib/source/library/lux/abstract/hash.lux @@ -1,17 +1,17 @@ (.using - [library - [lux "*"]] - [// - ["[0]" equivalence {"+" Equivalence}] - [functor - ["[0]" contravariant]]]) + [library + [lux "*"]] + [// + ["[0]" equivalence {"+" Equivalence}] + [functor + ["[0]" contravariant]]]) (type: .public (Hash a) (Interface - (: (Equivalence a) - &equivalence) - (: (-> a Nat) - hash))) + (is (Equivalence a) + &equivalence) + (is (-> a Nat) + hash))) (implementation: .public functor (contravariant.Functor Hash) diff --git a/stdlib/source/library/lux/abstract/interval.lux b/stdlib/source/library/lux/abstract/interval.lux index 68865241c..5ed94dafe 100644 --- a/stdlib/source/library/lux/abstract/interval.lux +++ b/stdlib/source/library/lux/abstract/interval.lux @@ -9,14 +9,14 @@ (type: .public (Interval a) (Interface - (: (Enum a) - &enum) + (is (Enum a) + &enum) - (: a - bottom) + (is a + bottom) - (: a - top))) + (is a + top))) (def: .public (between enum bottom top) (All (_ a) (-> (Enum a) a a (Interval a))) diff --git a/stdlib/source/library/lux/abstract/mix.lux b/stdlib/source/library/lux/abstract/mix.lux index 0a3c2088a..1c13dd985 100644 --- a/stdlib/source/library/lux/abstract/mix.lux +++ b/stdlib/source/library/lux/abstract/mix.lux @@ -6,9 +6,9 @@ (type: .public (Mix F) (Interface - (: (All (_ a b) - (-> (-> b a a) a (F b) a)) - mix))) + (is (All (_ a b) + (-> (-> b a a) a (F b) a)) + mix))) (def: .public (with_monoid monoid mix value) (All (_ F a) diff --git a/stdlib/source/library/lux/abstract/monad.lux b/stdlib/source/library/lux/abstract/monad.lux index 0802c0198..6a07fe8a2 100644 --- a/stdlib/source/library/lux/abstract/monad.lux +++ b/stdlib/source/library/lux/abstract/monad.lux @@ -45,47 +45,47 @@ (type: .public (Monad m) (Interface - (: (Functor m) - &functor) - (: (All (_ a) - (-> a (m a))) - in) - (: (All (_ a) - (-> (m (m a)) (m a))) - conjoint))) + (is (Functor m) + &functor) + (is (All (_ a) + (-> a (m a))) + in) + (is (All (_ a) + (-> (m (m a)) (m a))) + conjoint))) (macro: .public (do tokens state) - (case (: (Maybe [(Maybe Text) Code (List Code) Code]) - (case tokens - (pattern (list [_ {.#Tuple (list [_ {.#Symbol ["" name]}] monad)}] [_ {.#Tuple bindings}] body)) - {.#Some [{.#Some name} monad bindings body]} - - (pattern (list monad [_ {.#Tuple bindings}] body)) - {.#Some [{.#None} monad bindings body]} - - _ - {.#None})) + (case (is (Maybe [(Maybe Text) Code (List Code) Code]) + (case tokens + (pattern (list [_ {.#Tuple (list [_ {.#Symbol ["" name]}] monad)}] [_ {.#Tuple bindings}] body)) + {.#Some [{.#Some name} monad bindings body]} + + (pattern (list monad [_ {.#Tuple bindings}] body)) + {.#Some [{.#None} monad bindings body]} + + _ + {.#None})) {.#Some [?name monad bindings body]} (if (|> bindings list#size .int ("lux i64 %" +2) ("lux i64 =" +0)) (let [[module short] (symbol ..do) - symbol (: (-> Text Code) - (|>> ($_ "lux text concat" module " " short " ") [""] {.#Symbol} [location.dummy])) + symbol (is (-> Text Code) + (|>> ($_ "lux text concat" module " " short " ") [""] {.#Symbol} [location.dummy])) g!_ (symbol "_") g!each (symbol "each") g!conjoint (symbol "conjoint") - body' (list#mix (: (-> [Code Code] Code Code) - (function (_ binding body') - (with_expansions [<default> (` (|> (~ value) ((~ g!each) (function ((~ g!_) (~ var)) (~ body'))) (~ g!conjoint)))] - (let [[var value] binding] - (case var - [_ {.#Symbol ["" _]}] - <default> - - [_ {.#Symbol _}] - (` ((~ var) (~ value) (~ body'))) - - _ - <default>))))) + body' (list#mix (is (-> [Code Code] Code Code) + (function (_ binding body') + (with_expansions [<default> (` (|> (~ value) ((~ g!each) (function ((~ g!_) (~ var)) (~ body'))) (~ g!conjoint)))] + (let [[var value] binding] + (case var + [_ {.#Symbol ["" _]}] + <default> + + [_ {.#Symbol _}] + (` ((~ var) (~ value) (~ body'))) + + _ + <default>))))) body (reversed (pairs bindings)))] {.#Right [state (list (case ?name diff --git a/stdlib/source/library/lux/abstract/monad/indexed.lux b/stdlib/source/library/lux/abstract/monad/indexed.lux index 97cfae478..a6b99afc4 100644 --- a/stdlib/source/library/lux/abstract/monad/indexed.lux +++ b/stdlib/source/library/lux/abstract/monad/indexed.lux @@ -1,28 +1,28 @@ (.using - [library - [lux "*" - [control - ["<>" parser - ["<[0]>" code {"+" Parser}]]] - [data - [collection - ["[0]" list ("[1]#[0]" functor mix)]]] - ["[0]" macro - [syntax {"+" syntax:}] - ["[0]" code]]]] - ["[0]" //]) + [library + [lux "*" + [control + ["<>" parser + ["<[0]>" code {"+" Parser}]]] + [data + [collection + ["[0]" list ("[1]#[0]" functor mix)]]] + ["[0]" macro + [syntax {"+" syntax:}] + ["[0]" code]]]] + ["[0]" //]) (type: .public (IxMonad m) (Interface - (: (All (_ p a) - (-> a (m p p a))) - in) + (is (All (_ p a) + (-> a (m p p a))) + in) - (: (All (_ ii it io vi vo) - (-> (-> vi (m it io vo)) - (m ii it vi) - (m ii io vo))) - then))) + (is (All (_ ii it io vi vo) + (-> (-> vi (m it io vo)) + (m ii it vi) + (m ii io vo))) + then))) (type: Binding [Code Code]) diff --git a/stdlib/source/library/lux/abstract/monoid.lux b/stdlib/source/library/lux/abstract/monoid.lux index cf6e59cec..fe386411d 100644 --- a/stdlib/source/library/lux/abstract/monoid.lux +++ b/stdlib/source/library/lux/abstract/monoid.lux @@ -1,13 +1,13 @@ (.using - [library - [lux {"-" and}]]) + [library + [lux {"-" and}]]) (type: .public (Monoid a) (Interface - (: a - identity) - (: (-> a a a) - composite))) + (is a + identity) + (is (-> a a a) + composite))) (def: .public (and left right) (All (_ l r) (-> (Monoid l) (Monoid r) (Monoid [l r]))) diff --git a/stdlib/source/library/lux/abstract/order.lux b/stdlib/source/library/lux/abstract/order.lux index 610d477bb..e09899ad5 100644 --- a/stdlib/source/library/lux/abstract/order.lux +++ b/stdlib/source/library/lux/abstract/order.lux @@ -1,20 +1,20 @@ (.using - [library - [lux "*" - [control - ["[0]" function]]]] - [// - ["[0]" equivalence {"+" Equivalence}] - [functor - ["[0]" contravariant]]]) + [library + [lux "*" + [control + ["[0]" function]]]] + [// + ["[0]" equivalence {"+" Equivalence}] + [functor + ["[0]" contravariant]]]) (type: .public (Order a) (Interface - (: (Equivalence a) - &equivalence) + (is (Equivalence a) + &equivalence) - (: (-> a a Bit) - <))) + (is (-> a a Bit) + <))) (type: .public (Comparison a) (-> (Order a) a a Bit)) diff --git a/stdlib/source/library/lux/control/concatenative.lux b/stdlib/source/library/lux/control/concatenative.lux index 84383bba4..c4bf4c544 100644 --- a/stdlib/source/library/lux/control/concatenative.lux +++ b/stdlib/source/library/lux/control/concatenative.lux @@ -133,12 +133,12 @@ (with_symbols [g!_ g!func g!stack g!output] (monad.do [! meta.monad] [g!inputs (|> (macro.symbol "input") (list.repeated arity) (monad.all !))] - (in (list (` (: (All ((~ g!_) (~+ g!inputs) (~ g!output)) - (-> (-> (~+ g!inputs) (~ g!output)) - (=> [(~+ g!inputs)] [(~ g!output)]))) - (function ((~ g!_) (~ g!func)) - (function ((~ g!_) (~ (stack_mix g!inputs g!stack))) - [(~ g!stack) ((~ g!func) (~+ g!inputs))]))))))))) + (in (list (` (is (All ((~ g!_) (~+ g!inputs) (~ g!output)) + (-> (-> (~+ g!inputs) (~ g!output)) + (=> [(~+ g!inputs)] [(~ g!output)]))) + (function ((~ g!_) (~ g!func)) + (function ((~ g!_) (~ (stack_mix g!inputs g!stack))) + [(~ g!stack) ((~ g!func) (~+ g!inputs))]))))))))) (template [<arity>] [(`` (def: .public (~~ (template.symbol ["apply/" <arity>])) diff --git a/stdlib/source/library/lux/control/concurrency/actor.lux b/stdlib/source/library/lux/control/concurrency/actor.lux index cfa4fb11f..bdb3db4ce 100644 --- a/stdlib/source/library/lux/control/concurrency/actor.lux +++ b/stdlib/source/library/lux/control/concurrency/actor.lux @@ -28,8 +28,8 @@ [number ["n" nat]]] ["[0]" meta {"+" monad}] - [type {"+" :sharing} - ["[0]" abstract {"+" abstract: :representation :abstraction}]]]] + [type {"+" sharing} + ["[0]" abstract {"+" abstract: representation abstraction}]]]] [// ["[0]" atom {"+" Atom atom}] ["[0]" async {"+" Async Resolver} ("[1]#[0]" monad)] @@ -81,21 +81,21 @@ (def: .public (spawn! behavior init) (All (_ o s) (-> (Behavior o s) o (IO (Actor s)))) (io (let [[on_init on_mail] behavior - self (:sharing [o s] - (Behavior o s) - behavior - - (Actor s) - (:abstraction [#obituary (async.async []) - #mailbox (atom (async.async []))])) + self (sharing [o s] + (Behavior o s) + behavior + + (Actor s) + (abstraction [#obituary (async.async []) + #mailbox (atom (async.async []))])) process (loop [state (on_init init) - [|mailbox| _] (io.run! (atom.read! (the #mailbox (:representation self))))] + [|mailbox| _] (io.run! (atom.read! (the #mailbox (representation self))))] (do [! async.monad] [[head tail] |mailbox| ?state' (on_mail head state self)] (case ?state' {try.#Failure error} - (let [[_ resolve] (the #obituary (:representation self))] + (let [[_ resolve] (the #obituary (representation self))] (exec (io.run! (do io.monad [pending (..pending tail)] @@ -108,7 +108,7 @@ (def: .public (alive? actor) (All (_ s) (-> (Actor s) (IO Bit))) - (let [[obituary _] (the #obituary (:representation actor))] + (let [[obituary _] (the #obituary (representation actor))] (|> obituary async.value (# io.functor each @@ -121,12 +121,12 @@ (def: .public (obituary' actor) (All (_ s) (-> (Actor s) (IO (Maybe (Obituary s))))) - (let [[obituary _] (the #obituary (:representation actor))] + (let [[obituary _] (the #obituary (representation actor))] (async.value obituary))) (def: .public obituary (All (_ s) (-> (Actor s) (Async (Obituary s)))) - (|>> :representation + (|>> representation (the #obituary) product.left)) @@ -137,7 +137,7 @@ (if alive? (let [entry [mail (async.async [])]] (do ! - [|mailbox|&resolve (atom.read! (the #mailbox (:representation actor)))] + [|mailbox|&resolve (atom.read! (the #mailbox (representation actor)))] (loop [[|mailbox| resolve] |mailbox|&resolve] (do ! [|mailbox| (async.value |mailbox|)] @@ -147,7 +147,7 @@ [resolved? (resolve entry)] (if resolved? (do ! - [_ (atom.write! (product.right entry) (the #mailbox (:representation actor)))] + [_ (atom.write! (product.right entry) (the #mailbox (representation actor)))] (in {try.#Success []})) (again |mailbox|&resolve))) @@ -160,13 +160,13 @@ (def: (mail message) (All (_ s o) (-> (Message s o) [(Async (Try o)) (Mail s)])) - (let [[async resolve] (:sharing [s o] - (Message s o) - message - - [(Async (Try o)) - (Resolver (Try o))] - (async.async []))] + (let [[async resolve] (sharing [s o] + (Message s o) + message + + [(Async (Try o)) + (Resolver (Try o))] + (async.async []))] [async (function (_ state self) (do [! async.monad] @@ -271,7 +271,7 @@ (def: (~ export_policy) (~ g!actor) (All ((~ g!_) (~+ g!vars)) (..Behavior (~ state_type) ((~ g!type) (~+ g!vars)))) - [..#on_init (|>> ((~! abstract.:abstraction) (~ g!type))) + [..#on_init (|>> ((~! abstract.abstraction) (~ g!type))) ..#on_mail (~ (..on_mail g!_ ?on_mail))]) (~+ messages)))))))) @@ -279,12 +279,12 @@ (syntax: .public (actor [[state_type init] (<code>.tuple (<>.and <code>.any <code>.any)) ?on_mail on_mail^]) (with_symbols [g!_] - (in (list (` (: ((~! io.IO) (..Actor (~ state_type))) - (..spawn! (: (..Behavior (~ state_type) (~ state_type)) - [..#on_init (|>>) - ..#on_mail (~ (..on_mail g!_ ?on_mail))]) - (: (~ state_type) - (~ init))))))))) + (in (list (` (is ((~! io.IO) (..Actor (~ state_type))) + (..spawn! (is (..Behavior (~ state_type) (~ state_type)) + [..#on_init (|>>) + ..#on_mail (~ (..on_mail g!_ ?on_mail))]) + (is (~ state_type) + (~ init))))))))) (type: Signature (Record @@ -334,13 +334,13 @@ (..Message (~ (the abstract.#abstraction actor_scope)) (~ output_type)))) (function ((~ g!_) (~ g!state) (~ g!self)) - (let [(~ g!state) (:as (~ (the abstract.#representation actor_scope)) - (~ g!state))] + (let [(~ g!state) (as (~ (the abstract.#representation actor_scope)) + (~ g!state))] (|> (~ body) - (: ((~! async.Async) ((~! try.Try) [(~ (the abstract.#representation actor_scope)) - (~ output_type)]))) - (:as ((~! async.Async) ((~! try.Try) [(~ (the abstract.#abstraction actor_scope)) - (~ output_type)])))))))) + (is ((~! async.Async) ((~! try.Try) [(~ (the abstract.#representation actor_scope)) + (~ output_type)]))) + (as ((~! async.Async) ((~! try.Try) [(~ (the abstract.#abstraction actor_scope)) + (~ output_type)])))))))) ))))) (type: .public Stop @@ -351,10 +351,10 @@ (def: .public (observe! action channel actor) (All (_ e s) (-> (-> e Stop (Mail s)) (Channel e) (Actor s) (IO Any))) - (let [signal (: (Atom Bit) - (atom.atom ..continue!)) - stop (: Stop - (atom.write! ..stop! signal))] + (let [signal (is (Atom Bit) + (atom.atom ..continue!)) + stop (is Stop + (atom.write! ..stop! signal))] (frp.subscribe! (function (_ event) (do [! io.monad] [continue? (atom.read! signal)] diff --git a/stdlib/source/library/lux/control/concurrency/async.lux b/stdlib/source/library/lux/control/concurrency/async.lux index 32bc8cca1..6070efb3e 100644 --- a/stdlib/source/library/lux/control/concurrency/async.lux +++ b/stdlib/source/library/lux/control/concurrency/async.lux @@ -13,8 +13,8 @@ ["[0]" product]] [macro ["^" pattern]] - [type {"+" :sharing} - abstract]]] + [type {"+" sharing} + [abstract {"-" pattern}]]]] [// ["[0]" thread] ["[0]" atom {"+" Atom atom}]]) @@ -29,7 +29,7 @@ (def: (resolver async) (All (_ a) (-> (Async a) (Resolver a))) (function (resolve value) - (let [async (:representation async)] + (let [async (representation async)] (do [! io.monad] [(^.let old [_value _observers]) (atom.read! async)] (case _value @@ -49,23 +49,23 @@ (def: .public (resolved value) (All (_ a) (-> a (Async a))) - (:abstraction (atom [{.#Some value} (list)]))) + (abstraction (atom [{.#Some value} (list)]))) (def: .public (async _) (All (_ a) (-> Any [(Async a) (Resolver a)])) - (let [async (:abstraction (atom [{.#None} (list)]))] + (let [async (abstraction (atom [{.#None} (list)]))] [async (..resolver async)])) (def: .public value (All (_ a) (-> (Async a) (IO (Maybe a)))) - (|>> :representation + (|>> representation atom.read! (# io.functor each product.left))) (def: .public (upon! f async) (All (_ a) (-> (-> a (IO Any)) (Async a) (IO Any))) (do [! io.monad] - [.let [async (:representation async)] + [.let [async (representation async)] (^.let old [_value _observers]) (atom.read! async)] (case _value {.#Some value} @@ -77,7 +77,7 @@ [swapped? (atom.compare_and_swap! old new async)] (if swapped? (in []) - (upon! f (:abstraction async)))))))) + (upon! f (abstraction async)))))))) ) (def: .public resolved? @@ -128,13 +128,13 @@ (def: .public (and left right) (All (_ a b) (-> (Async a) (Async b) (Async [a b]))) - (let [[read! write!] (:sharing [a b] - [(Async a) (Async b)] - [left right] + (let [[read! write!] (sharing [a b] + [(Async a) (Async b)] + [left right] - [(Async [a b]) - (Resolver [a b])] - (..async [])) + [(Async [a b]) + (Resolver [a b])] + (..async [])) _ (io.run! (..upon! (function (_ left) (..upon! (function (_ right) (write! [left right])) diff --git a/stdlib/source/library/lux/control/concurrency/atom.lux b/stdlib/source/library/lux/control/concurrency/atom.lux index b15cecead..1fe0d8262 100644 --- a/stdlib/source/library/lux/control/concurrency/atom.lux +++ b/stdlib/source/library/lux/control/concurrency/atom.lux @@ -13,7 +13,7 @@ [collection ["[0]" array]]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) (with_expansions [<jvm> (as_is (ffi.import: (java/util/concurrent/atomic/AtomicReference a) "[1]::[0]" @@ -54,27 +54,27 @@ (def: .public (atom value) (All (_ a) (-> a (Atom a))) - (:abstraction (with_expansions [<jvm> (java/util/concurrent/atomic/AtomicReference::new value)] - (for @.old <jvm> - @.jvm <jvm> - (<write> 0 value (<new> 1)))))) + (abstraction (with_expansions [<jvm> (java/util/concurrent/atomic/AtomicReference::new value)] + (for @.old <jvm> + @.jvm <jvm> + (<write> 0 value (<new> 1)))))) (def: .public (read! atom) (All (_ a) (-> (Atom a) (IO a))) - (with_expansions [<jvm> (java/util/concurrent/atomic/AtomicReference::get (:representation atom))] + (with_expansions [<jvm> (java/util/concurrent/atomic/AtomicReference::get (representation atom))] (for @.old <jvm> @.jvm <jvm> - (io.io (<read> 0 (:representation atom)))))) + (io.io (<read> 0 (representation atom)))))) (def: .public (compare_and_swap! current new atom) (All (_ a) (-> a a (Atom a) (IO Bit))) - (io.io (with_expansions [<jvm> (ffi.of_boolean (java/util/concurrent/atomic/AtomicReference::compareAndSet current new (:representation atom)))] + (io.io (with_expansions [<jvm> (ffi.of_boolean (java/util/concurrent/atomic/AtomicReference::compareAndSet current new (representation atom)))] (for @.old <jvm> @.jvm <jvm> - (let [old (<read> 0 (:representation atom))] + (let [old (<read> 0 (representation atom))] (if (same? old current) (exec - (<write> 0 new (:representation atom)) + (<write> 0 new (representation atom)) true) false)))))) )) diff --git a/stdlib/source/library/lux/control/concurrency/frp.lux b/stdlib/source/library/lux/control/concurrency/frp.lux index c366207f9..361a2439b 100644 --- a/stdlib/source/library/lux/control/concurrency/frp.lux +++ b/stdlib/source/library/lux/control/concurrency/frp.lux @@ -11,8 +11,8 @@ ["[0]" try {"+" Try}] ["[0]" exception {"+" exception:}] ["[0]" io {"+" IO io}]] - [type {"+" :sharing} - abstract]]] + [type {"+" sharing} + [abstract {"-" pattern}]]]] [// ["[0]" atom {"+" Atom}] ["[0]" async {"+" Async} ("[1]#[0]" monad)]]) @@ -24,10 +24,10 @@ (type: .public (Sink a) (Interface - (: (IO (Try Any)) - close) - (: (-> a (IO (Try Any))) - feed))) + (is (IO (Try Any)) + close) + (is (-> a (IO (Try Any))) + feed))) (def: (sink resolve) (All (_ a) @@ -56,13 +56,13 @@ (loop [_ []] (do [! io.monad] [current (atom.read! sink) - .let [[next resolve_next] (:sharing [a] - (async.Resolver (Maybe [a (Channel a)])) - current - - [(Async (Maybe [a (Channel a)])) - (async.Resolver (Maybe [a (Channel a)]))] - (async.async []))] + .let [[next resolve_next] (sharing [a] + (async.Resolver (Maybe [a (Channel a)])) + current + + [(Async (Maybe [a (Channel a)])) + (async.Resolver (Maybe [a (Channel a)]))] + (async.async []))] fed? (current {.#Some [value next]})] (if fed? ... I fed the sink. @@ -123,28 +123,28 @@ (def: (conjoint mma) (let [[output sink] (channel [])] (exec - (: (Async Any) - (loop [mma mma] - (do [! async.monad] - [?mma mma] - (case ?mma - {.#Some [ma mma']} - (do ! - [_ (loop [ma ma] - (do ! - [?ma ma] - (case ?ma - {.#Some [a ma']} - (exec - (io.run! (# sink feed a)) - (again ma')) - - {.#None} - (in []))))] - (again mma')) - - {.#None} - (in (: Any (io.run! (# sink close)))))))) + (is (Async Any) + (loop [mma mma] + (do [! async.monad] + [?mma mma] + (case ?mma + {.#Some [ma mma']} + (do ! + [_ (loop [ma ma] + (do ! + [?ma ma] + (case ?ma + {.#Some [a ma']} + (exec + (io.run! (# sink feed a)) + (again ma')) + + {.#None} + (in []))))] + (again mma')) + + {.#None} + (in (is Any (io.run! (# sink close)))))))) output)))) (type: .public (Subscriber a) @@ -153,21 +153,21 @@ (def: .public (subscribe! subscriber channel) (All (_ a) (-> (Subscriber a) (Channel a) (IO Any))) (io (exec - (: (Async Any) - (loop [channel channel] - (do async.monad - [item channel] - (case item - {.#Some [head tail]} - (case (io.run! (subscriber head)) - {.#Some _} - (again tail) - - {.#None} - (in [])) - - {.#None} - (in []))))) + (is (Async Any) + (loop [channel channel] + (do async.monad + [item channel] + (case item + {.#Some [head tail]} + (case (io.run! (subscriber head)) + {.#Some _} + (again tail) + + {.#None} + (in [])) + + {.#None} + (in []))))) []))) (def: .public (only pass? channel) diff --git a/stdlib/source/library/lux/control/concurrency/semaphore.lux b/stdlib/source/library/lux/control/concurrency/semaphore.lux index 753b32dff..504e5472b 100644 --- a/stdlib/source/library/lux/control/concurrency/semaphore.lux +++ b/stdlib/source/library/lux/control/concurrency/semaphore.lux @@ -18,7 +18,7 @@ ["n" nat] ["i" int]]] [type - abstract + ["[0]" abstract {"-" pattern}] ["[0]" refinement]]]] [// ["[0]" atom {"+" Atom}] @@ -40,15 +40,15 @@ (-> Nat Semaphore) (let [max_positions (n.min initial_open_positions ..most_positions_possible)] - (:abstraction (atom.atom [#max_positions max_positions - #open_positions (.int max_positions) - #waiting_list queue.empty])))) + (abstraction (atom.atom [#max_positions max_positions + #open_positions (.int max_positions) + #waiting_list queue.empty])))) (def: .public (wait! semaphore) (Ex (_ k) (-> Semaphore (Async Any))) - (let [semaphore (:representation semaphore) - [signal sink] (: [(Async Any) (Resolver Any)] - (async.async []))] + (let [semaphore (representation semaphore) + [signal sink] (is [(Async Any) (Resolver Any)] + (async.async []))] (exec (io.run! (with_expansions [<had_open_position?> (as_is (the #open_positions) (i.> -1))] @@ -71,7 +71,7 @@ (def: .public (signal! semaphore) (Ex (_ k) (-> Semaphore (Async (Try Int)))) - (let [semaphore (:representation semaphore)] + (let [semaphore (representation semaphore)] (async.future (do [! io.monad] [[pre post] (atom.update! (function (_ state) @@ -99,15 +99,15 @@ (def: .public (mutex _) (-> Any Mutex) - (:abstraction (semaphore 1))) + (abstraction (semaphore 1))) (def: acquire! (-> Mutex (Async Any)) - (|>> :representation ..wait!)) + (|>> representation ..wait!)) (def: release! (-> Mutex (Async Any)) - (|>> :representation ..signal!)) + (|>> representation ..signal!)) (def: .public (synchronize! mutex procedure) (All (_ a) (-> Mutex (IO (Async a)) (Async a))) @@ -122,7 +122,7 @@ (refinement.refiner (n.> 0))) (type: .public Limit - (:~ (refinement.type limit))) + (~ (refinement.type limit))) (abstract: .public Barrier (Record @@ -133,10 +133,10 @@ (def: .public (barrier limit) (-> Limit Barrier) - (:abstraction [#limit limit - #count (atom.atom 0) - #start_turnstile (..semaphore 0) - #end_turnstile (..semaphore 0)])) + (abstraction [#limit limit + #count (atom.atom 0) + #start_turnstile (..semaphore 0) + #end_turnstile (..semaphore 0)])) (def: (un_block! times turnstile) (-> Nat Semaphore (Async Any)) @@ -148,7 +148,7 @@ (# async.monad in [])))) (template [<phase> <update> <goal> <turnstile>] - [(def: (<phase> (^:representation barrier)) + [(def: (<phase> (abstract.pattern barrier)) (-> Barrier (Async Any)) (do async.monad [.let [limit (refinement.value (the #limit barrier)) diff --git a/stdlib/source/library/lux/control/concurrency/stm.lux b/stdlib/source/library/lux/control/concurrency/stm.lux index 2be44daba..3668a2e9c 100644 --- a/stdlib/source/library/lux/control/concurrency/stm.lux +++ b/stdlib/source/library/lux/control/concurrency/stm.lux @@ -16,7 +16,7 @@ [macro ["^" pattern]] [type - abstract]]] + [abstract {"-" pattern}]]]] [// ["[0]" atom {"+" Atom atom}] ["[0]" async {"+" Async Resolver}] @@ -30,24 +30,24 @@ (def: .public (var value) (All (_ a) (-> a (Var a))) - (:abstraction (atom.atom [value (list)]))) + (abstraction (atom.atom [value (list)]))) (def: read! (All (_ a) (-> (Var a) a)) - (|>> :representation atom.read! io.run! product.left)) + (|>> representation atom.read! io.run! product.left)) (def: (un_follow! sink var) (All (_ a) (-> (Sink a) (Var a) (IO Any))) (do io.monad [_ (atom.update! (function (_ [value observers]) [value (list.only (|>> (same? sink) not) observers)]) - (:representation var))] + (representation var))] (in []))) (def: (write! new_value var) (All (_ a) (-> a (Var a) (IO Any))) (do [! io.monad] - [.let [var' (:representation var)] + [.let [var' (representation var)] (^.let old [old_value observers]) (atom.read! var') succeeded? (atom.compare_and_swap! old [new_value observers] var')] (if succeeded? @@ -71,7 +71,7 @@ [.let [[channel sink] (frp.channel [])] _ (atom.update! (function (_ [value observers]) [value {.#Item sink observers}]) - (:representation target))] + (representation target))] (in [channel sink]))) ) @@ -91,11 +91,11 @@ (All (_ a) (-> (Var a) Tx (Maybe a))) (|> tx (list.example (function (_ [_var _original _current]) - (same? (:as (Var Any) var) - (:as (Var Any) _var)))) + (same? (as (Var Any) var) + (as (Var Any) _var)))) (# maybe.monad each (function (_ [_var _original _current]) _current)) - :expected)) + as_expected)) (def: .public (read var) (All (_ a) (-> (Var a) (STM a))) @@ -116,11 +116,11 @@ {.#End} {.#Item [_var _original _current] tx'} - (if (same? (:as (Var Any) var) - (:as (Var Any) _var)) - {.#Item [#var (:as (Var Any) _var) - #original (:as Any _original) - #current (:as Any value)] + (if (same? (as (Var Any) var) + (as (Var Any) _var)) + {.#Item [#var (as (Var Any) _var) + #original (as Any _original) + #current (as Any value)] tx'} {.#Item [#var _var #original _original diff --git a/stdlib/source/library/lux/control/exception.lux b/stdlib/source/library/lux/control/exception.lux index ff25a2891..3d0be75fd 100644 --- a/stdlib/source/library/lux/control/exception.lux +++ b/stdlib/source/library/lux/control/exception.lux @@ -78,13 +78,13 @@ (def: exception (Parser [Code (List |type_variable|.Variable) [Text (List |input|.Input)] (Maybe Code)]) - (let [private (: (Parser [(List |type_variable|.Variable) [Text (List |input|.Input)] (Maybe Code)]) - ($_ <>.and - (<>.else (list) (<code>.tuple (<>.some |type_variable|.parser))) - (<>.either (<code>.form (<>.and <code>.local_symbol |input|.parser)) - (<>.and <code>.local_symbol (<>#in (list)))) - (<>.maybe <code>.any) - ))] + (let [private (is (Parser [(List |type_variable|.Variable) [Text (List |input|.Input)] (Maybe Code)]) + ($_ <>.and + (<>.else (list) (<code>.tuple (<>.some |type_variable|.parser))) + (<>.either (<code>.form (<>.and <code>.local_symbol |input|.parser)) + (<>.and <code>.local_symbol (<>#in (list)))) + (<>.maybe <code>.any) + ))] ($_ <>.either (<>.and <code>.any private) (<>.and (<>#in (` .private)) private) @@ -118,15 +118,15 @@ largest_header_size)) text.together (text#composite text.new_line)) - on_entry (: (-> [Text Text] Text) - (function (_ [header message]) - (let [padding (|> " " - (list.repeated (n.- (text.size header) - largest_header_size)) - text.together)] - (|> message - (text.replaced text.new_line on_new_line) - ($_ text#composite padding header header_separator)))))] + on_entry (is (-> [Text Text] Text) + (function (_ [header message]) + (let [padding (|> " " + (list.repeated (n.- (text.size header) + largest_header_size)) + text.together)] + (|> message + (text.replaced text.new_line on_new_line) + ($_ text#composite padding header header_separator)))))] (case entries {.#End} "" diff --git a/stdlib/source/library/lux/control/function/inline.lux b/stdlib/source/library/lux/control/function/inline.lux index ef0836888..f932b64e9 100644 --- a/stdlib/source/library/lux/control/function/inline.lux +++ b/stdlib/source/library/lux/control/function/inline.lux @@ -36,9 +36,9 @@ (monad.all !)) .let [inlined (` (("lux in-module" (~ (code.text @)) - (.: (~ type) - (.function ((~ (code.local_symbol name)) (~+ parameters)) - (~ term)))) + (.is (~ type) + (.function ((~ (code.local_symbol name)) (~+ parameters)) + (~ term)))) (~+ (list#each (function (_ g!parameter) (` ((~' ~) (~ g!parameter)))) g!parameters)))) diff --git a/stdlib/source/library/lux/control/function/memo.lux b/stdlib/source/library/lux/control/function/memo.lux index 381a1ba28..69b78c0c3 100644 --- a/stdlib/source/library/lux/control/function/memo.lux +++ b/stdlib/source/library/lux/control/function/memo.lux @@ -3,6 +3,7 @@ (.using [library [lux {"-" open} + ["[0]" type] [abstract [hash {"+" Hash}] [monad {"+" do}]] @@ -37,7 +38,7 @@ (def: .public (open memo) (All (_ i o) - (:let [Memory (Dictionary i o)] + (type.let [Memory (Dictionary i o)] (-> (Memo i o) (-> [Memory i] [Memory o])))) (let [memo (//.fixed (//.mixed ..memoization (//.of_recursive memo)))] (function (_ [memory input]) diff --git a/stdlib/source/library/lux/control/function/mutual.lux b/stdlib/source/library/lux/control/function/mutual.lux index ba9da195e..02f5eaabb 100644 --- a/stdlib/source/library/lux/control/function/mutual.lux +++ b/stdlib/source/library/lux/control/function/mutual.lux @@ -47,8 +47,8 @@ (.def: (macro g!context g!self) (-> Code Code Macro) - (<| (:as Macro) - (: Macro') + (<| (as Macro) + (is Macro') (function (_ parameters) (# meta.monad in (list (` (((~ g!self) (~ g!context)) (~+ parameters)))))))) @@ -60,9 +60,9 @@ {.#Item mutual {.#End}} (.let [g!name (|> mutual (the [#declaration declaration.#name]) code.local_symbol)] - (in (list (` (.let [(~ g!name) (: (~ (the #type mutual)) - (function (~ (declaration.format (the #declaration mutual))) - (~ (the #body mutual))))] + (in (list (` (.let [(~ g!name) (is (~ (the #type mutual)) + (function (~ (declaration.format (the #declaration mutual))) + (~ (the #body mutual))))] (~ body)))))) _ @@ -84,9 +84,9 @@ (..macro g!context g!name)]) (list.zipped/2 hidden_names functions)))] - (in (list (` (.let [(~ g!context) (: (Rec (~ g!context) - [(~+ context_types)]) - [(~+ definitions)]) + (in (list (` (.let [(~ g!context) (is (Rec (~ g!context) + [(~+ context_types)]) + [(~+ definitions)]) [(~+ user_names)] (.let [[(~+ user_names)] (~ g!context)] [(~+ (list#each (function (_ g!name) (` ((~ g!name) (~ g!context)))) @@ -138,9 +138,9 @@ functions)))] (in (list& (` (.def: (~ g!context) [(~+ (list#each (the [#mutual #type]) functions))] - (.let [(~ g!context) (: (Rec (~ g!context) - [(~+ context_types)]) - [(~+ definitions)]) + (.let [(~ g!context) (is (Rec (~ g!context) + [(~+ context_types)]) + [(~+ definitions)]) [(~+ user_names)] (~ g!context)] [(~+ (list#each (function (_ g!name) (` ((~ g!name) (~ g!context)))) diff --git a/stdlib/source/library/lux/control/io.lux b/stdlib/source/library/lux/control/io.lux index f112b4e1b..3edf5e3ee 100644 --- a/stdlib/source/library/lux/control/io.lux +++ b/stdlib/source/library/lux/control/io.lux @@ -1,34 +1,35 @@ (.using - [library - [lux "*" - [abstract - [functor {"+" Functor}] - [apply {"+" Apply}] - [monad {"+" Monad do}]] - [control - [parser - ["<[0]>" code]]] - [type - abstract] - [macro {"+" with_symbols} - [syntax {"+" syntax:}] - ["[0]" template]]]]) + [library + [lux "*" + [abstract + [functor {"+" Functor}] + [apply {"+" Apply}] + [monad {"+" Monad do}]] + [control + [parser + ["<[0]>" code]]] + [type + [abstract {"-" pattern}]] + [macro {"+" with_symbols} + [syntax {"+" syntax:}] + ["[0]" template]]]]) (abstract: .public (IO a) (-> Any a) (def: label (All (_ a) (-> (-> Any a) (IO a))) - (|>> :abstraction)) + (|>> abstraction)) (template: (!io computation) - [(:abstraction (template.with_locals [g!func g!arg] - (function (g!func g!arg) - computation)))]) + [(abstraction + (template.with_locals [g!func g!arg] + (function (g!func g!arg) + computation)))]) (template: (run!' io) ... creatio ex nihilo - [((:representation io) [])]) + [((representation io) [])]) (syntax: .public (io [computation <code>.any]) (with_symbols [g!func g!arg] diff --git a/stdlib/source/library/lux/control/lazy.lux b/stdlib/source/library/lux/control/lazy.lux index 01b3432cd..27131e570 100644 --- a/stdlib/source/library/lux/control/lazy.lux +++ b/stdlib/source/library/lux/control/lazy.lux @@ -14,34 +14,34 @@ ["[0]" atom]]] [macro {"+" with_symbols} [syntax {"+" syntax:}]] - [type {"+" :sharing} - abstract]]]) + [type {"+" sharing} + [abstract {"-" pattern}]]]]) (abstract: .public (Lazy a) (-> [] a) (def: (lazy' generator) (All (_ a) (-> (-> [] a) (Lazy a))) - (let [cache (atom.atom (:sharing [a] - (-> [] a) - generator + (let [cache (atom.atom (sharing [a] + (-> [] a) + generator - (Maybe a) - {.#None}))] - (:abstraction (function (_ _) - (case (io.run! (atom.read! cache)) - {.#Some value} - value + (Maybe a) + {.#None}))] + (abstraction (function (_ _) + (case (io.run! (atom.read! cache)) + {.#Some value} + value - _ - (let [value (generator [])] - (exec - (io.run! (atom.compare_and_swap! _ {.#Some value} cache)) - value))))))) + _ + (let [value (generator [])] + (exec + (io.run! (atom.compare_and_swap! _ {.#Some value} cache)) + value))))))) (def: .public (value lazy) (All (_ a) (-> (Lazy a) a)) - ((:representation lazy) []))) + ((representation lazy) []))) (syntax: .public (lazy [expression <code>.any]) (with_symbols [g!_] diff --git a/stdlib/source/library/lux/control/maybe.lux b/stdlib/source/library/lux/control/maybe.lux index cd963db10..98192ffa1 100644 --- a/stdlib/source/library/lux/control/maybe.lux +++ b/stdlib/source/library/lux/control/maybe.lux @@ -39,7 +39,7 @@ ... {.#None} it - (:expected it)))) + (as_expected it)))) (implementation: .public apply (Apply Maybe) @@ -69,7 +69,7 @@ ... {.#None} it - (:expected it)))) + (as_expected it)))) (implementation: .public (equivalence super) (All (_ a) (-> (Equivalence a) (Equivalence (Maybe a)))) @@ -119,7 +119,7 @@ ... {.#None} it - (in (:expected it)))))) + (in (as_expected it)))))) (def: .public (lifted monad) (All (_ M a) (-> (Monad M) (-> (M a) (M (Maybe a))))) @@ -128,7 +128,7 @@ (macro: .public (else tokens state) (case tokens (pattern (.list else maybe)) - (let [g!temp (: Code [location.dummy {.#Symbol ["" ""]}])] + (let [g!temp (is Code [location.dummy {.#Symbol ["" ""]}])] {.#Right [state (.list (` (.case (~ maybe) {.#Some (~ g!temp)} (~ g!temp) diff --git a/stdlib/source/library/lux/control/parser/binary.lux b/stdlib/source/library/lux/control/parser/binary.lux index ba305659a..b8c37c1bb 100644 --- a/stdlib/source/library/lux/control/parser/binary.lux +++ b/stdlib/source/library/lux/control/parser/binary.lux @@ -1,7 +1,7 @@ (.using [library [lux {"-" and or nat int rev list type symbol} - [type {"+" :sharing}] + [type {"+" sharing}] [abstract [hash {"+" Hash}] [monad {"+" do}]] @@ -111,8 +111,8 @@ (template: (!variant <case>+) [(do [! //.monad] - [flag (: (Parser Nat) - ..bits/8)] + [flag (is (Parser Nat) + ..bits/8)] (with_expansions [<case>+' (template.spliced <case>+)] (case flag (^.template [<number> <tag> <parser>] @@ -144,8 +144,8 @@ (def: .public bit (Parser Bit) (do //.monad - [value (: (Parser Nat) - ..bits/8)] + [value (is (Parser Nat) + ..bits/8)] (case value 0 (in #0) 1 (in #1) @@ -192,15 +192,15 @@ [(def: .public (<name> valueP) (All (_ v) (-> (Parser v) (Parser (Sequence v)))) (do //.monad - [amount (: (Parser Nat) - <bits>)] + [amount (is (Parser Nat) + <bits>)] (loop [index 0 - output (:sharing [v] - (Parser v) - valueP - - (Sequence v) - sequence.empty)] + output (sharing [v] + (Parser v) + valueP + + (Sequence v) + sequence.empty)] (if (n.< amount index) (do //.monad [value valueP] diff --git a/stdlib/source/library/lux/control/parser/type.lux b/stdlib/source/library/lux/control/parser/type.lux index 8550ce29f..6587f2270 100644 --- a/stdlib/source/library/lux/control/parser/type.lux +++ b/stdlib/source/library/lux/control/parser/type.lux @@ -186,7 +186,7 @@ .let [funcL (label funcI) [all_varsL env'] (loop [current_arg 0 env' env - all_varsL (: (List Code) (list))] + all_varsL (is (List Code) (list))] (if (n.< num_args current_arg) (if (n.= 0 current_arg) (let [varL (label (++ funcI))] diff --git a/stdlib/source/library/lux/control/security/capability.lux b/stdlib/source/library/lux/control/security/capability.lux index f66ce87c4..b23ddf2e6 100644 --- a/stdlib/source/library/lux/control/security/capability.lux +++ b/stdlib/source/library/lux/control/security/capability.lux @@ -1,27 +1,27 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]] - [control - ["[0]" io {"+" IO}] - ["<>" parser - ["<c>" code]] - [concurrency - ["[0]" async {"+" Async}]]] - [data - [text - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [type - abstract] - ["[0]" meta] - ["[0]" macro - ["[0]" code] - [syntax {"+" syntax:} - ["|[0]|" export] - ["|[0]|" declaration]]]]]) + [library + [lux "*" + [abstract + [monad {"+" do}]] + [control + ["[0]" io {"+" IO}] + ["<>" parser + ["<c>" code]] + [concurrency + ["[0]" async {"+" Async}]]] + [data + [text + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [type + [abstract {"-" pattern}]] + ["[0]" meta] + ["[0]" macro + ["[0]" code] + [syntax {"+" syntax:} + ["|[0]|" export] + ["|[0]|" declaration]]]]]) (abstract: .public (Capability brand input output) (-> input output) @@ -30,14 +30,14 @@ (All (_ brand input output) (-> (-> input output) (Capability brand input output))) - (|>> :abstraction)) + (|>> abstraction)) (def: .public (use capability input) (All (_ brand input output) (-> (Capability brand input output) input output)) - ((:representation capability) input)) + ((representation capability) input)) (syntax: .public (capability: [[export_policy declaration [forger input output]] (|export|.parser @@ -65,5 +65,5 @@ (All (_ brand input output) (-> (Capability brand input (IO output)) (Capability brand input (Async output)))) - (..capability (|>> ((:representation capability)) async.future))) + (..capability (|>> ((representation capability)) async.future))) ) diff --git a/stdlib/source/library/lux/control/security/policy.lux b/stdlib/source/library/lux/control/security/policy.lux index 17a7ff1d8..d3165f0c6 100644 --- a/stdlib/source/library/lux/control/security/policy.lux +++ b/stdlib/source/library/lux/control/security/policy.lux @@ -1,12 +1,12 @@ (.using - [library - [lux "*" - [abstract - [functor {"+" Functor}] - [apply {"+" Apply}] - [monad {"+" Monad}]] - [type - abstract]]]) + [library + [lux "*" + [abstract + [functor {"+" Functor}] + [apply {"+" Apply}] + [monad {"+" Monad}]] + [type + [abstract {"-" pattern}]]]]) (abstract: .public (Policy brand value label) value @@ -39,8 +39,8 @@ (def: privilege Privilege - [#can_upgrade (|>> :abstraction) - #can_downgrade (|>> :representation)]) + [#can_upgrade (|>> abstraction) + #can_downgrade (|>> representation)]) (def: .public (with_policy context) (All (_ brand scope) @@ -55,25 +55,25 @@ (constructor (All (_ value) (Policy brand value label)))))) (implementation: .public functor - (:~ (..of_policy Functor)) + (~ (..of_policy Functor)) (def: (each f fa) - (|> fa :representation f :abstraction))) + (|> fa representation f abstraction))) (implementation: .public apply - (:~ (..of_policy Apply)) + (~ (..of_policy Apply)) (def: &functor ..functor) (def: (on fa ff) - (:abstraction ((:representation ff) (:representation fa))))) + (abstraction ((representation ff) (representation fa))))) (implementation: .public monad - (:~ (..of_policy Monad)) + (~ (..of_policy Monad)) (def: &functor ..functor) - (def: in (|>> :abstraction)) - (def: conjoint (|>> :representation))) + (def: in (|>> abstraction)) + (def: conjoint (|>> representation))) ) (template [<brand> <value> <upgrade> <downgrade>] diff --git a/stdlib/source/library/lux/control/thread.lux b/stdlib/source/library/lux/control/thread.lux index b07c213a1..95c7ddc69 100644 --- a/stdlib/source/library/lux/control/thread.lux +++ b/stdlib/source/library/lux/control/thread.lux @@ -12,7 +12,7 @@ [collection ["[0]" array {"+" Array}]]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) (type: .public (Thread ! a) (-> ! a)) @@ -25,33 +25,33 @@ (function (_ !) (|> (array.empty 1) (array.write! 0 init) - :abstraction))) + abstraction))) (def: .public (read! box) (All (_ ! a) (-> (Box ! a) (Thread ! a))) (function (_ !) (for @.old - ("jvm aaload" (:representation box) 0) + ("jvm aaload" (representation box) 0) @.jvm ("jvm array read object" (|> 0 - (:as (Primitive "java.lang.Long")) + (as (Primitive "java.lang.Long")) "jvm object cast" "jvm conversion long-to-int") - (:representation box)) + (representation box)) - @.js ("js array read" 0 (:representation box)) - @.python ("python array read" 0 (:representation box)) - @.lua ("lua array read" 0 (:representation box)) - @.ruby ("ruby array read" 0 (:representation box)) - @.php ("php array read" 0 (:representation box)) - @.scheme ("scheme array read" 0 (:representation box))))) + @.js ("js array read" 0 (representation box)) + @.python ("python array read" 0 (representation box)) + @.lua ("lua array read" 0 (representation box)) + @.ruby ("ruby array read" 0 (representation box)) + @.php ("php array read" 0 (representation box)) + @.scheme ("scheme array read" 0 (representation box))))) (def: .public (write! value box) (All (_ a) (-> a (All (_ !) (-> (Box ! a) (Thread ! Any))))) (function (_ !) - (|> box :representation (array.write! 0 value) :abstraction))) + (|> box representation (array.write! 0 value) abstraction))) ) (def: .public (result thread) diff --git a/stdlib/source/library/lux/control/try.lux b/stdlib/source/library/lux/control/try.lux index 6f50ef702..4da14bb92 100644 --- a/stdlib/source/library/lux/control/try.lux +++ b/stdlib/source/library/lux/control/try.lux @@ -25,7 +25,7 @@ ... {#Failure msg} it - (:expected it)))) + (as_expected it)))) (implementation: .public apply (Apply Try) @@ -41,11 +41,11 @@ ... {#Failure msg} it - (:expected it)) + (as_expected it)) ... {#Failure msg} it - (:expected it)))) + (as_expected it)))) (implementation: .public monad (Monad Try) @@ -62,7 +62,7 @@ ... {#Failure msg} it - (:expected it)))) + (as_expected it)))) (implementation: .public (with monad) ... TODO: Replace (All (_ a) (! (Try a))) with (functor.Then ! Try) @@ -85,7 +85,7 @@ ... {#Failure error} it - (in (:expected it)))))) + (in (as_expected it)))))) (def: .public (lifted monad) (All (_ ! a) (-> (Monad !) (-> (! a) (! (Try a))))) diff --git a/stdlib/source/library/lux/control/writer.lux b/stdlib/source/library/lux/control/writer.lux index 852891255..bfbf6183e 100644 --- a/stdlib/source/library/lux/control/writer.lux +++ b/stdlib/source/library/lux/control/writer.lux @@ -63,12 +63,12 @@ (def: (conjoint MlMla) (do monad [[l1 Mla] (for @.old - (: {.#Apply (Writer (:parameter 0) - {.#Apply (Writer (:parameter 0) - (:parameter 2)) - (:parameter 1)}) - (:parameter 1)} - MlMla) + (is {.#Apply (Writer (parameter 0) + {.#Apply (Writer (parameter 0) + (parameter 2)) + (parameter 1)}) + (parameter 1)} + MlMla) ... On new compiler MlMla) [l2 a] Mla] diff --git a/stdlib/source/library/lux/data/collection/bits.lux b/stdlib/source/library/lux/data/collection/bits.lux index 45527975a..797bb5981 100644 --- a/stdlib/source/library/lux/data/collection/bits.lux +++ b/stdlib/source/library/lux/data/collection/bits.lux @@ -83,7 +83,7 @@ chunk (|> (if (same? ..empty output) - (: Bits (array.empty size|output)) + (is Bits (array.empty size|output)) output) (array.write! idx|output (.i64 chunk)) (again (-- size|output)))) @@ -124,7 +124,7 @@ chunk (if (n.> 0 size|output) (|> (if (same? ..empty output) - (: Bits (array.empty size|output)) + (is Bits (array.empty size|output)) output) (array.write! idx (.i64 chunk)) (again (-- size|output))) @@ -151,7 +151,7 @@ chunk (|> (if (same? ..empty output) - (: Bits (array.empty size|output)) + (is Bits (array.empty size|output)) output) (array.write! idx (.i64 chunk)) (again (-- size|output)))) diff --git a/stdlib/source/library/lux/data/collection/list.lux b/stdlib/source/library/lux/data/collection/list.lux index 4b0071ddd..450bfea3a 100644 --- a/stdlib/source/library/lux/data/collection/list.lux +++ b/stdlib/source/library/lux/data/collection/list.lux @@ -382,10 +382,10 @@ (if (< x x') [{.#Item x' pre} post] [pre {.#Item x' post}])) - (`` [(: (~~ (:of xs)) - (list)) - (: (~~ (:of xs)) - (list))]) + (`` [(is (~~ (type_of xs)) + (list)) + (is (~~ (type_of xs)) + (list))]) xs')] ($_ composite (sorted < pre) (list x) (sorted < post))))) @@ -460,9 +460,9 @@ (if (n.> 0 num_lists) (let [(open "[0]") ..functor indices (..indices num_lists) - type_vars (: (List Code) (each (|>> nat#encoded symbol$) indices)) + type_vars (is (List Code) (each (|>> nat#encoded symbol$) indices)) zipped_type (` (.All ((~ (symbol$ "0_")) (~+ type_vars)) - (-> (~+ (each (: (-> Code Code) (function (_ var) (` (List (~ var))))) + (-> (~+ (each (is (-> Code Code) (function (_ var) (` (List (~ var))))) type_vars)) (List [(~+ type_vars)])))) vars+lists (|> indices @@ -476,15 +476,15 @@ g!step (symbol$ "0step0") g!blank (symbol$ "0,0") list_vars (each product.right vars+lists) - code (` (: (~ zipped_type) - (function ((~ g!step) (~+ list_vars)) - (case [(~+ list_vars)] - (~ pattern) - {.#Item [(~+ (each product.left vars+lists))] - ((~ g!step) (~+ list_vars))} - - (~ g!blank) - {.#End}))))] + code (` (is (~ zipped_type) + (function ((~ g!step) (~+ list_vars)) + (case [(~+ list_vars)] + (~ pattern) + {.#Item [(~+ (each product.left vars+lists))] + ((~ g!step) (~+ list_vars))} + + (~ g!blank) + {.#End}))))] {.#Right [state (list code)]}) {.#Left "Cannot zipped 0 lists."}) @@ -502,10 +502,10 @@ indices (..indices num_lists) g!return_type (symbol$ "0return_type0") g!func (symbol$ "0func0") - type_vars (: (List Code) (each (|>> nat#encoded symbol$) indices)) + type_vars (is (List Code) (each (|>> nat#encoded symbol$) indices)) zipped_type (` (All ((~ (symbol$ "0_")) (~+ type_vars) (~ g!return_type)) (-> (-> (~+ type_vars) (~ g!return_type)) - (~+ (each (: (-> Code Code) (function (_ var) (` (List (~ var))))) + (~+ (each (is (-> Code Code) (function (_ var) (` (List (~ var))))) type_vars)) (List (~ g!return_type))))) vars+lists (|> indices @@ -519,15 +519,15 @@ g!step (symbol$ "0step0") g!blank (symbol$ "0,0") list_vars (each product.right vars+lists) - code (` (: (~ zipped_type) - (function ((~ g!step) (~ g!func) (~+ list_vars)) - (case [(~+ list_vars)] - (~ pattern) - {.#Item ((~ g!func) (~+ (each product.left vars+lists))) - ((~ g!step) (~ g!func) (~+ list_vars))} - - (~ g!blank) - {.#End}))))] + code (` (is (~ zipped_type) + (function ((~ g!step) (~ g!func) (~+ list_vars)) + (case [(~+ list_vars)] + (~ pattern) + {.#Item ((~ g!func) (~+ (each product.left vars+lists))) + ((~ g!step) (~ g!func) (~+ list_vars))} + + (~ g!blank) + {.#End}))))] {.#Right [state (list code)]}) {.#Left "Cannot zipped_with 0 lists."}) @@ -585,9 +585,9 @@ (do [! monad] [lMla MlMla ... TODO: Remove this version ASAP and use one below. - lla (for @.old (: {.#Apply (type (List (List (:parameter 1)))) - (:parameter 0)} - (monad.all ! lMla)) + lla (for @.old (is {.#Apply (type (List (List (parameter 1)))) + (parameter 0)} + (monad.all ! lMla)) (monad.all ! lMla))] (in (..together lla))))) diff --git a/stdlib/source/library/lux/data/collection/queue/priority.lux b/stdlib/source/library/lux/data/collection/queue/priority.lux index 86a1dc237..102472124 100644 --- a/stdlib/source/library/lux/data/collection/queue/priority.lux +++ b/stdlib/source/library/lux/data/collection/queue/priority.lux @@ -1,20 +1,20 @@ (.using - [library - [lux "*" - [abstract - [equivalence {"+" Equivalence}] - [monad {"+" do}]] - [control - ["[0]" maybe]] - [data - [collection - ["[0]" tree "_" - ["[1]" finger {"+" Tree}]]]] - [math - [number - ["n" nat ("[1]#[0]" interval)]]] - [type {"+" :by_example} - [abstract {"+" abstract: :abstraction :representation}]]]]) + [library + [lux "*" + [abstract + [equivalence {"+" Equivalence}] + [monad {"+" do}]] + [control + ["[0]" maybe]] + [data + [collection + ["[0]" tree "_" + ["[1]" finger {"+" Tree}]]]] + [math + [number + ["n" nat ("[1]#[0]" interval)]]] + [type {"+" by_example} + [abstract {"+" abstract: abstraction representation}]]]]) (type: .public Priority Nat) @@ -31,29 +31,29 @@ (tree.builder n.maximum)) (def: :@: - (:by_example [@] - (tree.Builder @ Priority) - ..builder - - @)) + (by_example [@] + (tree.Builder @ Priority) + ..builder + + @)) (abstract: .public (Queue a) (Maybe (Tree :@: Priority a)) (def: .public empty Queue - (:abstraction {.#None})) + (abstraction {.#None})) (def: .public (front queue) (All (_ a) (-> (Queue a) (Maybe a))) (do maybe.monad - [tree (:representation queue)] + [tree (representation queue)] (tree.one (n.= (tree.tag tree)) tree))) (def: .public (size queue) (All (_ a) (-> (Queue a) Nat)) - (case (:representation queue) + (case (representation queue) {.#None} 0 @@ -68,7 +68,7 @@ (def: .public (member? equivalence queue member) (All (_ a) (-> (Equivalence a) (Queue a) a Bit)) - (case (:representation queue) + (case (representation queue) {.#None} false @@ -84,9 +84,9 @@ (def: .public (next queue) (All (_ a) (-> (Queue a) (Queue a))) - (:abstraction + (abstraction (do maybe.monad - [tree (:representation queue) + [tree (representation queue) .let [highest_priority (tree.tag tree)]] (loop [node tree] (case (tree.root node) @@ -113,8 +113,8 @@ (def: .public (end priority value queue) (All (_ a) (-> Priority a (Queue a) (Queue a))) (let [addition (# ..builder leaf priority value)] - (:abstraction - (case (:representation queue) + (abstraction + (case (representation queue) {.#None} {.#Some addition} diff --git a/stdlib/source/library/lux/data/collection/sequence.lux b/stdlib/source/library/lux/data/collection/sequence.lux index 34a3e512d..285a65109 100644 --- a/stdlib/source/library/lux/data/collection/sequence.lux +++ b/stdlib/source/library/lux/data/collection/sequence.lux @@ -225,8 +225,8 @@ ... If so, a brand-new root must be established, that is ... 1-level taller. (|> sequence - (.has #root (|> (`` (: (Hierarchy (~~ (:of val))) - (empty_hierarchy []))) + (.has #root (|> (`` (is (Hierarchy (~~ (type_of val))) + (empty_hierarchy []))) (array.has! 0 {#Hierarchy (the #root sequence)}) (array.has! 1 (..path (the #level sequence) (the #tail sequence))))) (.revised #level level_up)) @@ -291,9 +291,9 @@ {try.#Success (if (n.< (tail_off sequence_size) idx) (.revised #root (hierarchy#has (the #level sequence) idx val) sequence) - (.revised #tail (`` (: (-> (Base (~~ (:of val))) - (Base (~~ (:of val)))) - (|>> array.clone (array.has! (branch_idx idx) val)))) + (.revised #tail (`` (is (-> (Base (~~ (type_of val))) + (Base (~~ (type_of val)))) + (|>> array.clone (array.has! (branch_idx idx) val)))) sequence))} (exception.except ..index_out_of_bounds [sequence idx])))) @@ -485,15 +485,15 @@ [(def: .public <name> (All (_ a) (-> (Predicate a) (Sequence a) Bit)) - (let [help (: (All (_ a) - (-> (Predicate a) (Node a) Bit)) - (function (help predicate node) - (case node - {#Base base} - (<array> predicate base) - - {#Hierarchy hierarchy} - (<array> (help predicate) hierarchy))))] + (let [help (is (All (_ a) + (-> (Predicate a) (Node a) Bit)) + (function (help predicate node) + (case node + {#Base base} + (<array> predicate base) + + {#Hierarchy hierarchy} + (<array> (help predicate) hierarchy))))] (function (<name> predicate sequence) (let [(open "_[0]") sequence] (<op> (help predicate {#Hierarchy _#root}) diff --git a/stdlib/source/library/lux/data/collection/set/multi.lux b/stdlib/source/library/lux/data/collection/set/multi.lux index ea7fd7df0..6de0ed5df 100644 --- a/stdlib/source/library/lux/data/collection/set/multi.lux +++ b/stdlib/source/library/lux/data/collection/set/multi.lux @@ -14,7 +14,7 @@ [number ["n" nat]]] [type - [abstract {"+" abstract: :abstraction :representation ^:representation}]]]] + ["[0]" abstract {"+" abstract: abstraction representation}]]]] ["[0]" // [// ["[0]" list ("[1]#[0]" mix monoid)] @@ -25,42 +25,42 @@ (def: .public empty (All (_ a) (-> (Hash a) (Set a))) - (|>> dictionary.empty :abstraction)) + (|>> dictionary.empty abstraction)) (def: .public size (All (_ a) (-> (Set a) Nat)) - (|>> :representation dictionary.values (list#mix n.+ 0))) + (|>> representation dictionary.values (list#mix n.+ 0))) (def: .public (has multiplicity elem set) (All (_ a) (-> Nat a (Set a) (Set a))) (case multiplicity 0 set _ (|> set - :representation + representation (dictionary.revised' elem 0 (n.+ multiplicity)) - :abstraction))) + abstraction))) (def: .public (lacks multiplicity elem set) (All (_ a) (-> Nat a (Set a) (Set a))) (case multiplicity 0 set - _ (case (dictionary.value elem (:representation set)) + _ (case (dictionary.value elem (representation set)) {.#Some current} - (:abstraction + (abstraction (if (n.> multiplicity current) - (dictionary.revised elem (n.- multiplicity) (:representation set)) - (dictionary.lacks elem (:representation set)))) + (dictionary.revised elem (n.- multiplicity) (representation set)) + (dictionary.lacks elem (representation set)))) {.#None} set))) (def: .public (multiplicity set elem) (All (_ a) (-> (Set a) a Nat)) - (|> set :representation (dictionary.value elem) (maybe.else 0))) + (|> set representation (dictionary.value elem) (maybe.else 0))) (def: .public list (All (_ a) (-> (Set a) (List a))) - (|>> :representation + (|>> representation dictionary.entries (list#mix (function (_ [elem multiplicity] output) (list#composite (list.repeated multiplicity elem) output)) @@ -69,13 +69,13 @@ (template [<name> <composite>] [(def: .public (<name> parameter subject) (All (_ a) (-> (Set a) (Set a) (Set a))) - (:abstraction (dictionary.merged_with <composite> (:representation parameter) (:representation subject))))] + (abstraction (dictionary.merged_with <composite> (representation parameter) (representation subject))))] [union n.max] [sum n.+] ) - (def: .public (intersection parameter (^:representation subject)) + (def: .public (intersection parameter (abstract.pattern subject)) (All (_ a) (-> (Set a) (Set a) (Set a))) (list#mix (function (_ [elem multiplicity] output) (..has (n.min (..multiplicity parameter elem) @@ -88,7 +88,7 @@ (def: .public (difference parameter subject) (All (_ a) (-> (Set a) (Set a) (Set a))) (|> parameter - :representation + representation dictionary.entries (list#mix (function (_ [elem multiplicity] output) (..lacks multiplicity elem output)) @@ -97,7 +97,7 @@ (def: .public (sub? reference subject) (All (_ a) (-> (Set a) (Set a) Bit)) (|> subject - :representation + representation dictionary.entries (list.every? (function (_ [elem multiplicity]) (|> elem @@ -106,7 +106,7 @@ (def: .public (support set) (All (_ a) (-> (Set a) (//.Set a))) - (let [(^.let set [hash _]) (:representation set)] + (let [(^.let set [hash _]) (representation set)] (|> set dictionary.keys (//.of_list hash)))) @@ -114,9 +114,9 @@ (implementation: .public equivalence (All (_ a) (Equivalence (Set a))) - (def: (= (^:representation reference) sample) + (def: (= (abstract.pattern reference) sample) (and (n.= (dictionary.size reference) - (dictionary.size (:representation sample))) + (dictionary.size (representation sample))) (|> reference dictionary.entries (list.every? (function (_ [elem multiplicity]) @@ -129,7 +129,7 @@ (def: &equivalence ..equivalence) - (def: (hash (^:representation set)) + (def: (hash (abstract.pattern set)) (let [[hash _] set] (list#mix (function (_ [elem multiplicity] acc) (|> elem (# hash hash) (n.* multiplicity) (n.+ acc))) diff --git a/stdlib/source/library/lux/data/collection/set/ordered.lux b/stdlib/source/library/lux/data/collection/set/ordered.lux index 5827e0993..c73e4d04a 100644 --- a/stdlib/source/library/lux/data/collection/set/ordered.lux +++ b/stdlib/source/library/lux/data/collection/set/ordered.lux @@ -10,23 +10,23 @@ [dictionary ["/" ordered]]]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) (abstract: .public (Set a) (/.Dictionary a a) (def: .public empty (All (_ a) (-> (Order a) (Set a))) - (|>> /.empty :abstraction)) + (|>> /.empty abstraction)) (def: .public (member? set elem) (All (_ a) (-> (Set a) a Bit)) - (/.key? (:representation set) elem)) + (/.key? (representation set) elem)) (template [<type> <name> <alias>] [(def: .public <name> (All (_ a) (-> (Set a) <type>)) - (|>> :representation <alias>))] + (|>> representation <alias>))] [(Maybe a) min /.min] [(Maybe a) max /.max] @@ -36,15 +36,15 @@ (def: .public (has elem set) (All (_ a) (-> a (Set a) (Set a))) - (|> set :representation (/.has elem elem) :abstraction)) + (|> set representation (/.has elem elem) abstraction)) (def: .public (lacks elem set) (All (_ a) (-> a (Set a) (Set a))) - (|> set :representation (/.lacks elem) :abstraction)) + (|> set representation (/.lacks elem) abstraction)) (def: .public list (All (_ a) (-> (Set a) (List a))) - (|>> :representation /.keys)) + (|>> representation /.keys)) (def: .public (of_list &order list) (All (_ a) (-> (Order a) (List a) (Set a))) @@ -58,19 +58,19 @@ (All (_ a) (-> (Set a) (Set a) (Set a))) (|> (..list right) (list.only (..member? left)) - (..of_list (the /.#&order (:representation right))))) + (..of_list (the /.#&order (representation right))))) (def: .public (difference param subject) (All (_ a) (-> (Set a) (Set a) (Set a))) (|> (..list subject) (list.only (|>> (..member? param) not)) - (..of_list (the /.#&order (:representation subject))))) + (..of_list (the /.#&order (representation subject))))) (implementation: .public equivalence (All (_ a) (Equivalence (Set a))) (def: (= reference sample) - (# (list.equivalence (# (:representation reference) &equivalence)) + (# (list.equivalence (# (representation reference) &equivalence)) = (..list reference) (..list sample)))) ) diff --git a/stdlib/source/library/lux/data/collection/stack.lux b/stdlib/source/library/lux/data/collection/stack.lux index 5c096b40b..fa7a5c589 100644 --- a/stdlib/source/library/lux/data/collection/stack.lux +++ b/stdlib/source/library/lux/data/collection/stack.lux @@ -1,33 +1,33 @@ (.using - [library - [lux "*" - [abstract - [equivalence {"+" Equivalence}] - [functor {"+" Functor}]] - [data - [collection - ["//" list]]] - [type - abstract]]]) + [library + [lux "*" + [abstract + [equivalence {"+" Equivalence}] + [functor {"+" Functor}]] + [data + [collection + ["//" list]]] + [type + [abstract {"-" pattern}]]]]) (abstract: .public (Stack a) (List a) (def: .public empty Stack - (:abstraction (list))) + (abstraction (list))) (def: .public size (All (_ a) (-> (Stack a) Nat)) - (|>> :representation //.size)) + (|>> representation //.size)) (def: .public empty? (All (_ a) (-> (Stack a) Bit)) - (|>> :representation //.empty?)) + (|>> representation //.empty?)) (def: .public (value stack) (All (_ a) (-> (Stack a) (Maybe a))) - (case (:representation stack) + (case (representation stack) {.#End} {.#None} @@ -36,16 +36,16 @@ (def: .public (next stack) (All (_ a) (-> (Stack a) (Maybe [a (Stack a)]))) - (case (:representation stack) + (case (representation stack) {.#End} {.#None} {.#Item top stack'} - {.#Some [top (:abstraction stack')]})) + {.#Some [top (abstraction stack')]})) (def: .public (top value stack) (All (_ a) (-> a (Stack a) (Stack a))) - (:abstraction {.#Item value (:representation stack)})) + (abstraction {.#Item value (representation stack)})) (implementation: .public (equivalence super) (All (_ a) @@ -53,14 +53,14 @@ (Equivalence (Stack a)))) (def: (= reference subject) - (# (//.equivalence super) = (:representation reference) (:representation subject)))) + (# (//.equivalence super) = (representation reference) (representation subject)))) (implementation: .public functor (Functor Stack) (def: (each f value) (|> value - :representation + representation (# //.functor each f) - :abstraction))) + abstraction))) ) diff --git a/stdlib/source/library/lux/data/collection/tree/finger.lux b/stdlib/source/library/lux/data/collection/tree/finger.lux index 30486daff..26caf5317 100644 --- a/stdlib/source/library/lux/data/collection/tree/finger.lux +++ b/stdlib/source/library/lux/data/collection/tree/finger.lux @@ -8,7 +8,7 @@ [collection ["[0]" list ("[1]#[0]" monoid)]]] [type - [abstract {"+" abstract: :abstraction :representation}]]]]) + [abstract {"+" abstract: abstraction representation}]]]]) ... https://en.wikipedia.org/wiki/Finger_tree (abstract: .public (Tree @ t v) @@ -20,19 +20,19 @@ (type: .public (Builder @ t) (Interface - (: (All (_ v) - (-> t v (Tree @ t v))) - leaf) - (: (All (_ v) - (-> (Tree @ t v) - (Tree @ t v) - (Tree @ t v))) - branch))) + (is (All (_ v) + (-> t v (Tree @ t v))) + leaf) + (is (All (_ v) + (-> (Tree @ t v) + (Tree @ t v) + (Tree @ t v))) + branch))) (template [<name> <tag> <output>] [(def: .public <name> (All (_ @ t v) (-> (Tree @ t v) <output>)) - (|>> :representation (the <tag>)))] + (|>> representation (the <tag>)))] [tag #tag t] [root #root (Either v [(Tree @ t v) (Tree @ t v)])] @@ -42,20 +42,20 @@ (All (_ t) (Ex (_ @) (-> (Monoid t) (Builder @ t)))) (def: (leaf tag value) - (:abstraction + (abstraction [#monoid monoid #tag tag #root {.#Left value}])) (def: (branch left right) - (:abstraction + (abstraction [#monoid monoid #tag (# monoid composite (..tag left) (..tag right)) #root {.#Right [left right]}]))) (def: .public (value tree) (All (_ @ t v) (-> (Tree @ t v) v)) - (case (the #root (:representation tree)) + (case (the #root (representation tree)) {0 #0 value} value @@ -64,9 +64,9 @@ (def: .public (tags tree) (All (_ @ t v) (-> (Tree @ t v) (List t))) - (case (the #root (:representation tree)) + (case (the #root (representation tree)) {0 #0 value} - (list (the #tag (:representation tree))) + (list (the #tag (representation tree))) {0 #1 [left right]} (list#composite (tags left) @@ -74,7 +74,7 @@ (def: .public (values tree) (All (_ @ t v) (-> (Tree @ t v) (List v))) - (case (the #root (:representation tree)) + (case (the #root (representation tree)) {0 #0 value} (list value) @@ -84,7 +84,7 @@ (def: .public (one predicate tree) (All (_ @ t v) (-> (Predicate t) (Tree @ t v) (Maybe v))) - (let [[monoid tag root] (:representation tree)] + (let [[monoid tag root] (representation tree)] (if (predicate tag) (let [(open "tag//[0]") monoid] (loop [_tag tag//identity @@ -96,8 +96,8 @@ {0 #1 [left right]} (let [shifted_tag (tag//composite _tag (..tag left))] (if (predicate shifted_tag) - (again _tag (the #root (:representation left))) - (again shifted_tag (the #root (:representation right)))))))) + (again _tag (the #root (representation left))) + (again shifted_tag (the #root (representation right)))))))) {.#None}))) ) diff --git a/stdlib/source/library/lux/data/collection/tree/zipper.lux b/stdlib/source/library/lux/data/collection/tree/zipper.lux index e4fd53818..9986e63a8 100644 --- a/stdlib/source/library/lux/data/collection/tree/zipper.lux +++ b/stdlib/source/library/lux/data/collection/tree/zipper.lux @@ -104,11 +104,11 @@ [family (the #family zipper)] (in (let [(open "_[0]") family] (for @.old - (revised #node (: (-> (Tree (:parameter 0)) - (Tree (:parameter 0))) - (has //.#children (list#composite (list.reversed _#lefts) - {.#Item (the #node zipper) - _#rights}))) + (revised #node (is (-> (Tree (parameter 0)) + (Tree (parameter 0))) + (has //.#children (list#composite (list.reversed _#lefts) + {.#Item (the #node zipper) + _#rights}))) _#parent) (has [#node //.#children] (list#composite (list.reversed _#lefts) @@ -128,10 +128,10 @@ (has <side> side') (revised <op_side> (|>> {.#Item (the #node zipper)})))} #node next] - (let [move (: (All (_ a) (-> (List (Tree a)) (Zipper a) (Family Zipper a) (Family Zipper a))) - (function (_ side' zipper) - (|>> (has <side> side') - (revised <op_side> (|>> {.#Item (the #node zipper)})))))] + (let [move (is (All (_ a) (-> (List (Tree a)) (Zipper a) (Family Zipper a) (Family Zipper a))) + (function (_ side' zipper) + (|>> (has <side> side') + (revised <op_side> (|>> {.#Item (the #node zipper)})))))] [#family {.#Some (move side' zipper family)} #node next]))} @@ -158,11 +158,11 @@ (revised <op_side> (|>> {.#Item (the #node zipper)} (list#composite prevs))))} #node last] - (let [move (: (All (_ a) (-> (List (Tree a)) (Zipper a) (Family Zipper a) (Family Zipper a))) - (function (_ prevs zipper) - (|>> (has <side> {.#End}) - (revised <op_side> (|>> {.#Item (the #node zipper)} - (list#composite prevs))))))] + (let [move (is (All (_ a) (-> (List (Tree a)) (Zipper a) (Family Zipper a) (Family Zipper a))) + (function (_ prevs zipper) + (|>> (has <side> {.#End}) + (revised <op_side> (|>> {.#Item (the #node zipper)} + (list#composite prevs))))))] [#family {.#Some (move prevs zipper family)} #node last]))})))] @@ -310,12 +310,12 @@ (the [#node //.#value])) (def: (disjoint (open "_[0]")) - (let [tree_splitter (: (All (_ a) (-> (Tree a) (Tree (Zipper a)))) - (function (tree_splitter tree) - [//.#value (..zipper tree) - //.#children (|> tree - (the //.#children) - (list#each tree_splitter))]))] + (let [tree_splitter (is (All (_ a) (-> (Tree a) (Tree (Zipper a)))) + (function (tree_splitter tree) + [//.#value (..zipper tree) + //.#children (|> tree + (the //.#children) + (list#each tree_splitter))]))] [#family (maybe#each (function (_ (open "_[0]")) [..#parent (disjoint _#parent) ..#lefts (list#each tree_splitter _#lefts) diff --git a/stdlib/source/library/lux/data/color.lux b/stdlib/source/library/lux/data/color.lux index 093a2b6ba..c5cf003ef 100644 --- a/stdlib/source/library/lux/data/color.lux +++ b/stdlib/source/library/lux/data/color.lux @@ -16,7 +16,7 @@ ["[0]" rev ("[1]#[0]" interval)] ["[0]" i64]]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) (def: rgb_limit 256) (def: top (-- rgb_limit)) @@ -56,20 +56,20 @@ (def: .public (of_rgb [red green blue]) (-> RGB Color) - (:abstraction [#red (n.% ..rgb_limit red) - #green (n.% ..rgb_limit green) - #blue (n.% ..rgb_limit blue)])) + (abstraction [#red (n.% ..rgb_limit red) + #green (n.% ..rgb_limit green) + #blue (n.% ..rgb_limit blue)])) (def: .public rgb (-> Color RGB) - (|>> :representation)) + (|>> representation)) (implementation: .public equivalence (Equivalence Color) (def: (= reference sample) - (let [[rR gR bR] (:representation reference) - [rS gS bS] (:representation sample)] + (let [[rR gR bR] (representation reference) + [rS gS bS] (representation sample)] (and (n.= rR rS) (n.= gR gS) (n.= bR bS))))) @@ -80,7 +80,7 @@ (def: &equivalence ..equivalence) (def: (hash value) - (let [[r g b] (:representation value)] + (let [[r g b] (representation value)] ($_ i64.or (i64.left_shifted 16 r) (i64.left_shifted 8 g) @@ -104,11 +104,11 @@ (def: identity ..black) (def: (composite left right) - (let [[lR lG lB] (:representation left) - [rR rG rB] (:representation right)] - (:abstraction [#red (n.max lR rR) - #green (n.max lG rG) - #blue (n.max lB rB)])))) + (let [[lR lG lB] (representation left) + [rR rG rB] (representation right)] + (abstraction [#red (n.max lR rR) + #green (n.max lG rG) + #blue (n.max lB rB)])))) (def: (opposite_intensity value) (-> Nat Nat) @@ -116,10 +116,10 @@ (def: .public (complement color) (-> Color Color) - (let [[red green blue] (:representation color)] - (:abstraction [#red (opposite_intensity red) - #green (opposite_intensity green) - #blue (opposite_intensity blue)]))) + (let [[red green blue] (representation color)] + (abstraction [#red (opposite_intensity red) + #green (opposite_intensity green) + #blue (opposite_intensity blue)]))) (implementation: .public subtraction (Monoid Color) @@ -127,11 +127,11 @@ (def: identity ..white) (def: (composite left right) - (let [[lR lG lB] (:representation (..complement left)) - [rR rG rB] (:representation right)] - (:abstraction [#red (n.min lR rR) - #green (n.min lG rG) - #blue (n.min lB rB)])))) + (let [[lR lG lB] (representation (..complement left)) + [rR rG rB] (representation right)] + (abstraction [#red (n.min lR rR) + #green (n.min lG rG) + #blue (n.min lB rB)])))) ) (def: .public (hsl color) @@ -304,12 +304,12 @@ (-> Frac Color Color Color) (let [dS (..normal ratio) dE (|> +1.0 (f.- dS)) - interpolated' (: (-> Nat Nat Nat) - (function (_ end start) - (|> (|> start .int int.frac (f.* dS)) - (f.+ (|> end .int int.frac (f.* dE))) - f.int - .nat))) + interpolated' (is (-> Nat Nat Nat) + (function (_ end start) + (|> (|> start .int int.frac (f.* dS)) + (f.+ (|> end .int int.frac (f.* dE))) + f.int + .nat))) [redS greenS blueS] (rgb start) [redE greenE blueE] (rgb end)] (of_rgb [#red (interpolated' redE redS) diff --git a/stdlib/source/library/lux/data/format/css.lux b/stdlib/source/library/lux/data/format/css.lux index 649e50f5d..dc42d50d2 100644 --- a/stdlib/source/library/lux/data/format/css.lux +++ b/stdlib/source/library/lux/data/format/css.lux @@ -13,7 +13,7 @@ [number ["[0]" nat]]] [type - [abstract {"-" Frame}]] + [abstract {"-" Frame pattern}]] [world [net {"+" URL}]]]] ["[0]" / "_" @@ -32,25 +32,25 @@ (def: .public css (-> (CSS Any) Text) - (|>> :representation)) + (|>> representation)) (def: .public empty (CSS Any) - (:abstraction "")) + (abstraction "")) (type: .public Style (List (Ex (_ brand) [(Property brand) (Value brand)]))) (def: .public (rule selector style) (-> (Selector Any) Style (CSS Common)) - (:abstraction (format (/selector.selector selector) "{" (/style.inline (/style.style style)) "}"))) + (abstraction (format (/selector.selector selector) "{" (/style.inline (/style.style style)) "}"))) (def: .public char_set (-> Encoding (CSS Special)) (|>> encoding.name %.text (text.enclosed ["@charset " ";"]) - :abstraction)) + abstraction)) (def: .public (font font) (-> Font (CSS Special)) @@ -73,18 +73,18 @@ text.together (text.enclosed ["{" "}"]) (format "@font-face") - :abstraction))) + abstraction))) (def: .public (import url query) (-> URL (Maybe Query) (CSS Special)) - (:abstraction (format (format "@import url(" (%.text url) ")") - (case query - {.#Some query} - (format " " (/query.query query)) - - {.#None} - "") - ";"))) + (abstraction (format (format "@import url(" (%.text url) ")") + (case query + {.#Some query} + (format " " (/query.query query)) + + {.#None} + "") + ";"))) (def: separator text.new_line) @@ -96,20 +96,20 @@ (def: .public (key_frames animation frames) (-> (Value Animation) (List Frame) (CSS Special)) - (:abstraction (format "@keyframes " (/value.value animation) " {" - (|> frames - (list#each (function (_ frame) - (format (/value.value (the #when frame)) " {" - (/style.inline (/style.style (the #what frame))) - "}"))) - (text.interposed ..separator)) - "}"))) + (abstraction (format "@keyframes " (/value.value animation) " {" + (|> frames + (list#each (function (_ frame) + (format (/value.value (the #when frame)) " {" + (/style.inline (/style.style (the #what frame))) + "}"))) + (text.interposed ..separator)) + "}"))) (template: (!composite <pre> <post>) - [(:abstraction - (format (:representation <pre>) + [(abstraction + (format (representation <pre>) ..separator - (:representation <post>)))]) + (representation <post>)))]) (def: .public (and pre post) (All (_ kind) (-> (CSS kind) (CSS kind) (CSS kind))) @@ -118,14 +118,14 @@ (def: .public (in_context combinator selector css) (-> Combinator (Selector Any) (CSS Common) (CSS Common)) (|> css - :representation + representation (text.all_split_by ..separator) (list#each (let [prefix (|> selector (combinator (/selector.tag "")) /selector.selector)] (|>> (format prefix)))) (text.interposed ..separator) - :abstraction)) + abstraction)) (def: .public (dependent combinator selector style inner) (-> Combinator (Selector Any) Style (CSS Common) (CSS Common)) @@ -145,14 +145,14 @@ (All (_ kind) (-> (Specializer kind) (Selector (Generic Any)) (CSS Common) (CSS Common))) (|> css - :representation + representation (text.all_split_by ..separator) (list#each (let [prefix (|> selector - (specializer (:expected (/selector.tag ""))) + (specializer (as_expected (/selector.tag ""))) /selector.selector)] (|>> (format prefix)))) (text.interposed ..separator) - :abstraction)) + abstraction)) (def: .public (specialized combinator selector style inner) (All (_ kind) diff --git a/stdlib/source/library/lux/data/format/css/class.lux b/stdlib/source/library/lux/data/format/css/class.lux index e3b1a67b7..6d056d1ac 100644 --- a/stdlib/source/library/lux/data/format/css/class.lux +++ b/stdlib/source/library/lux/data/format/css/class.lux @@ -11,18 +11,18 @@ [syntax {"+" syntax:}] ["[0]" code]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) (abstract: .public Class Text (def: .public class (-> Class Text) - (|>> :representation)) + (|>> representation)) (def: .public custom (-> Text Class) - (|>> :abstraction)) + (|>> abstraction)) (syntax: .public (generic []) (do meta.monad diff --git a/stdlib/source/library/lux/data/format/css/id.lux b/stdlib/source/library/lux/data/format/css/id.lux index c5a6f5862..1ace95687 100644 --- a/stdlib/source/library/lux/data/format/css/id.lux +++ b/stdlib/source/library/lux/data/format/css/id.lux @@ -11,18 +11,18 @@ [syntax {"+" syntax:}] ["[0]" code]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) (abstract: .public ID Text (def: .public id (-> ID Text) - (|>> :representation)) + (|>> representation)) (def: .public custom (-> Text ID) - (|>> :abstraction)) + (|>> abstraction)) (syntax: .public (generic []) (do meta.monad diff --git a/stdlib/source/library/lux/data/format/css/property.lux b/stdlib/source/library/lux/data/format/css/property.lux index 155297f84..65b4bfd5f 100644 --- a/stdlib/source/library/lux/data/format/css/property.lux +++ b/stdlib/source/library/lux/data/format/css/property.lux @@ -1,58 +1,58 @@ (.using - [library - [lux {"-" All Location} - [control - [parser - ["s" code]]] - [data - ["[0]" text]] - [type - abstract] - [macro - ["[0]" template] - ["[0]" code] - [syntax {"+" syntax:}]]]] - [// - [value {"+" All - Number - Length Thickness Time - Color - Location Fit - Slice - Alignment Animation_Direction - Animation Animation_Fill - Column_Fill Column_Span - Iteration Count - Play - Timing Visibility Attachment - Blend Span Image - Angle Repeat Border - Collapse Box_Decoration_Break Caption - Float Clear - Content - Cursor - Shadow Clip - Text_Direction - Display Empty - Filter - Flex_Direction Flex_Wrap - Font Font_Kerning Font_Size Font_Stretch Font_Style Font_Weight Font_Variant - Grid Grid_Content Grid_Flow Grid_Span Grid_Template - Hanging_Punctuation Hyphens Isolation - List_Style_Position List_Style_Type - Overflow Page_Break Pointer_Events - Position - Quotes - Resize Scroll_Behavior Table_Layout - Text_Align Text_Align_Last - Text_Decoration_Line Text_Decoration_Style - Text_Justification Text_Overflow Text_Transform - Transform Transform_Origin Transform_Style - Transition - Bidi User_Select - Vertical_Align - White_Space Word_Break Word_Wrap Writing_Mode - Z_Index}]]) + [library + [lux {"-" All Location} + [control + [parser + ["s" code]]] + [data + ["[0]" text]] + [type + [abstract {"-" pattern}]] + [macro + ["[0]" template] + ["[0]" code] + [syntax {"+" syntax:}]]]] + [// + [value {"+" All + Number + Length Thickness Time + Color + Location Fit + Slice + Alignment Animation_Direction + Animation Animation_Fill + Column_Fill Column_Span + Iteration Count + Play + Timing Visibility Attachment + Blend Span Image + Angle Repeat Border + Collapse Box_Decoration_Break Caption + Float Clear + Content + Cursor + Shadow Clip + Text_Direction + Display Empty + Filter + Flex_Direction Flex_Wrap + Font Font_Kerning Font_Size Font_Stretch Font_Style Font_Weight Font_Variant + Grid Grid_Content Grid_Flow Grid_Span Grid_Template + Hanging_Punctuation Hyphens Isolation + List_Style_Position List_Style_Type + Overflow Page_Break Pointer_Events + Position + Quotes + Resize Scroll_Behavior Table_Layout + Text_Align Text_Align_Last + Text_Decoration_Line Text_Decoration_Style + Text_Justification Text_Overflow Text_Transform + Transform Transform_Origin Transform_Style + Transition + Bidi User_Select + Vertical_Align + White_Space Word_Break Word_Wrap Writing_Mode + Z_Index}]]) (syntax: (text_symbol [symbol s.text]) (in (list (code.local_symbol (text.replaced "-" "_" symbol))))) @@ -62,13 +62,13 @@ (def: .public name (-> (Property Any) Text) - (|>> :representation)) + (|>> representation)) (template [<brand> <alias>+ <property>+] [(`` (template [<alias> <property>] [(def: .public <alias> (Property <brand>) - (:abstraction <property>))] + (abstraction <property>))] (~~ (template.spliced <alias>+)))) @@ -76,7 +76,7 @@ (template [<property>] [(`` (def: .public (~~ (text_symbol <property>)) (Property <brand>) - (:abstraction <property>)))] + (abstraction <property>)))] <rows>))] diff --git a/stdlib/source/library/lux/data/format/css/query.lux b/stdlib/source/library/lux/data/format/css/query.lux index 8251fcb06..7e2272c4a 100644 --- a/stdlib/source/library/lux/data/format/css/query.lux +++ b/stdlib/source/library/lux/data/format/css/query.lux @@ -1,25 +1,25 @@ (.using - [library - [lux {"-" and or not} - [control - [parser - ["s" code]]] - [data - ["[0]" text - ["%" format {"+" format}]]] - [macro - ["[0]" template] - ["[0]" code] - [syntax {"+" syntax:}]] - [type - abstract]]] - ["[0]" // "_" - ["[1][0]" value {"+" Value Length Count Resolution Ratio - Orientation Scan Boolean Update - Block_Overflow Inline_Overflow - Display_Mode Color_Gamut Inverted_Colors - Pointer Hover - Light Scripting Motion Color_Scheme}]]) + [library + [lux {"-" and or not} + [control + [parser + ["s" code]]] + [data + ["[0]" text + ["%" format {"+" format}]]] + [macro + ["[0]" template] + ["[0]" code] + [syntax {"+" syntax:}]] + [type + [abstract {"-" pattern}]]]] + ["[0]" // "_" + ["[1][0]" value {"+" Value Length Count Resolution Ratio + Orientation Scan Boolean Update + Block_Overflow Inline_Overflow + Display_Mode Color_Gamut Inverted_Colors + Pointer Hover + Light Scripting Motion Color_Scheme}]]) (syntax: (text_symbol [symbol s.text]) (in (list (code.local_symbol (text.replaced "-" "_" symbol))))) @@ -29,12 +29,12 @@ (def: .public media (-> Media Text) - (|>> :representation)) + (|>> representation)) (template [<media>] [(`` (def: .public (~~ (text_symbol <media>)) Media - (:abstraction <media>)))] + (abstraction <media>)))] ["all"] ["print"] @@ -47,12 +47,12 @@ (def: .public feature (-> Feature Text) - (|>> :representation)) + (|>> representation)) (template [<feature> <brand>] [(`` (def: .public ((~~ (text_symbol <feature>)) input) (-> (Value <brand>) Feature) - (:abstraction (format "(" <feature> ": " (//value.value input) ")"))))] + (abstraction (format "(" <feature> ": " (//value.value input) ")"))))] ["min-color" Count] ["color" Count] @@ -107,12 +107,12 @@ (def: .public query (-> Query Text) - (|>> :representation)) + (|>> representation)) (template [<name> <operator>] [(def: .public <name> (-> Media Query) - (|>> ..media (format <operator>) :abstraction))] + (|>> ..media (format <operator>) abstraction))] [except "not "] [only "only "] @@ -120,14 +120,14 @@ (def: .public not (-> Feature Query) - (|>> ..feature (format "not ") :abstraction)) + (|>> ..feature (format "not ") abstraction)) (template [<name> <operator>] [(def: .public (<name> left right) (-> Query Query Query) - (:abstraction (format (:representation left) - <operator> - (:representation right))))] + (abstraction (format (representation left) + <operator> + (representation right))))] [and " and "] [or " or "] diff --git a/stdlib/source/library/lux/data/format/css/selector.lux b/stdlib/source/library/lux/data/format/css/selector.lux index 47a394603..fc53d8731 100644 --- a/stdlib/source/library/lux/data/format/css/selector.lux +++ b/stdlib/source/library/lux/data/format/css/selector.lux @@ -9,7 +9,7 @@ [number ["i" int]]] [type - abstract] + [abstract {"-" pattern}]] [macro ["[0]" template]]]] ["[0]" // "_" @@ -40,20 +40,20 @@ (def: .public selector (-> (Selector Any) Text) - (|>> :representation)) + (|>> representation)) (def: .public any (Selector Cannot_Chain) - (:abstraction "*")) + (abstraction "*")) (def: .public tag (-> Tag (Selector Cannot_Chain)) - (|>> :abstraction)) + (|>> abstraction)) (template [<name> <type> <prefix> <kind> <out>] [(def: .public <name> (-> <type> (Selector <kind>)) - (|>> <out> (format <prefix>) :abstraction))] + (|>> <out> (format <prefix>) abstraction))] [id ID "#" Unique //id.id] [class Class "." Can_Chain //class.class] @@ -63,9 +63,9 @@ [(`` (template [<combinator> <name>] [(def: .public (<name> right left) (-> (Selector <right>) (Selector <left>) (Selector Composite)) - (:abstraction (format (:representation left) - <combinator> - (:representation right))))] + (abstraction (format (representation left) + <combinator> + (representation right))))] (~~ (template.spliced <combinator>+))))] @@ -91,12 +91,12 @@ (def: .public (with? attribute) (-> Attribute (Selector Can_Chain)) - (:abstraction (format "[" attribute "]"))) + (abstraction (format "[" attribute "]"))) (template [<check> <name>] [(def: .public (<name> attribute value) (-> Attribute Text (Selector Can_Chain)) - (:abstraction (format "[" attribute <check> value "]")))] + (abstraction (format "[" attribute <check> value "]")))] ["=" same?] ["~=" has?] @@ -110,7 +110,7 @@ [(`` (template [<name> <pseudo>] [(def: .public <name> (Selector <kind>) - (:abstraction <pseudo>))] + (abstraction <pseudo>))] (~~ (template.spliced <pseudo>+))))] @@ -158,24 +158,24 @@ locale.code (text.enclosed ["(" ")"]) (format ":lang") - :abstraction)) + abstraction)) (def: .public not (-> (Selector Any) (Selector Can_Chain)) - (|>> :representation + (|>> representation (text.enclosed ["(" ")"]) (format ":not") - :abstraction)) + abstraction)) (abstract: .public Index Text (def: .public index (-> Nat Index) - (|>> %.nat :abstraction)) + (|>> %.nat abstraction)) (template [<name> <index>] - [(def: .public <name> Index (:abstraction <index>))] + [(def: .public <name> Index (abstraction <index>))] [odd "odd"] [even "even"] @@ -189,18 +189,18 @@ (def: .public (formula input) (-> Formula Index) (let [(open "_[0]") input] - (:abstraction (format (if (i.< +0 _#variable) - (%.int _#variable) - (%.nat (.nat _#variable))) - (%.int _#constant))))) + (abstraction (format (if (i.< +0 _#variable) + (%.int _#variable) + (%.nat (.nat _#variable))) + (%.int _#constant))))) (template [<name> <pseudo>] [(def: .public (<name> index) (-> Index (Selector Can_Chain)) - (|> (:representation index) + (|> (representation index) (text.enclosed ["(" ")"]) (format <pseudo>) - (:abstraction Selector)))] + (abstraction Selector)))] [nth_child ":nth-child"] [nth_last_child ":nth-last-child"] diff --git a/stdlib/source/library/lux/data/format/css/style.lux b/stdlib/source/library/lux/data/format/css/style.lux index 8ec6a207f..42c7d07cb 100644 --- a/stdlib/source/library/lux/data/format/css/style.lux +++ b/stdlib/source/library/lux/data/format/css/style.lux @@ -7,7 +7,7 @@ [collection ["[0]" list ("[1]#[0]" mix)]]] [type - abstract]]] + [abstract {"-" pattern}]]]] ["[0]" // "_" ["[1][0]" value {"+" Value}] ["[1][0]" property {"+" Property}]]) @@ -17,19 +17,19 @@ (def: .public empty Style - (:abstraction "")) + (abstraction "")) (def: .public (with [property value]) (All (_ brand) (-> [(Property brand) (Value brand)] (-> Style Style))) - (|>> :representation + (|>> representation (format (//property.name property) ": " (//value.value value) ";") - :abstraction)) + abstraction)) (def: .public inline (-> Style Text) - (|>> :representation)) + (|>> representation)) (def: .public (style config) (-> (List (Ex (_ brand) [(Property brand) (Value brand)])) diff --git a/stdlib/source/library/lux/data/format/css/value.lux b/stdlib/source/library/lux/data/format/css/value.lux index b48718568..dad95e9b8 100644 --- a/stdlib/source/library/lux/data/format/css/value.lux +++ b/stdlib/source/library/lux/data/format/css/value.lux @@ -23,7 +23,7 @@ ["r" rev] ["f" frac]]] [type - abstract] + [abstract {"-" pattern}]] [world [net {"+" URL}]]]] [// @@ -38,10 +38,10 @@ (def: .public <out> (-> <abstraction> <representation>) - (|>> :representation)) + (|>> representation)) (`` (template [<name> <value>] - [(def: .public <name> <abstraction> (:abstraction <value>))] + [(def: .public <name> <abstraction> (abstraction <value>))] (~~ (template.spliced <sample>+)) )) @@ -51,9 +51,9 @@ (template: (multi: <multi> <type> <separator>) [(def: .public (<multi> pre post) (-> (Value <type>) (Value <type>) (Value <type>)) - (:abstraction (format (:representation pre) - <separator> - (:representation post))))]) + (abstraction (format (representation pre) + <separator> + (representation post))))]) (def: (%number value) (Format Frac) @@ -67,10 +67,10 @@ (def: .public value (-> (Value Any) Text) - (|>> :representation)) + (|>> representation)) (template [<name> <value>] - [(def: .public <name> Value (:abstraction <value>))] + [(def: .public <name> Value (abstraction <value>))] [initial "initial"] [inherit "inherit"] @@ -97,7 +97,7 @@ (`` (template [<name> <value>] [(def: .public <name> (Value <brand>) - (:abstraction <value>))] + (abstraction <value>))] (~~ (template.spliced <alias>+)))) @@ -105,7 +105,7 @@ (template [<value>] [(`` (def: .public (~~ (..text_symbol <value>)) (Value <brand>) - (:abstraction <value>)))] + (abstraction <value>)))] <rows>))] @@ -788,7 +788,7 @@ (text.interposed ..value_separator) (text.enclosed ["(" ")"]) (format name) - :abstraction)) + abstraction)) (enumeration: Step Text step @@ -809,7 +809,7 @@ (template [<name> <brand>] [(def: .public <name> (-> Nat (Value <brand>)) - (|>> %.nat :abstraction))] + (|>> %.nat abstraction))] [iteration Iteration] [count Count] @@ -819,7 +819,7 @@ (def: .public animation (-> Label (Value Animation)) - (|>> :abstraction)) + (|>> abstraction)) (def: .public (rgb color) (-> color.Color (Value Color)) @@ -842,7 +842,7 @@ (template [<name> <suffix>] [(def: .public (<name> value) (-> Frac (Value Length)) - (:abstraction (format (%number value) <suffix>)))] + (abstraction (format (%number value) <suffix>)))] [em "em"] [ex "ex"] @@ -871,10 +871,10 @@ (template [<name> <suffix>] [(def: .public (<name> value) (-> Int (Value Time)) - (:abstraction (format (if (i.< +0 value) - (%.int value) - (%.nat (.nat value))) - <suffix>)))] + (abstraction (format (if (i.< +0 value) + (%.int value) + (%.nat (.nat value))) + <suffix>)))] [seconds "s"] @@ -883,50 +883,50 @@ (def: .public thickness (-> (Value Length) (Value Thickness)) - (|>> :transmutation)) + (|>> transmutation)) (def: slice_separator " ") (def: .public (slice_number/2 horizontal vertical) (-> Nat Nat (Value Slice)) - (:abstraction (format (%.nat horizontal) ..slice_separator - (%.nat vertical)))) + (abstraction (format (%.nat horizontal) ..slice_separator + (%.nat vertical)))) (abstract: .public Stop Text (def: .public stop (-> (Value Color) Stop) - (|>> (:representation Value) (:abstraction Stop))) + (|>> (representation Value) (abstraction Stop))) (def: stop_separator " ") (def: .public (single_stop length color) (-> (Value Length) (Value Color) Stop) - (:abstraction (format (:representation Value color) ..stop_separator - (:representation Value length)))) + (abstraction (format (representation Value color) ..stop_separator + (representation Value length)))) (def: .public (double_stop start end color) (-> (Value Length) (Value Length) (Value Color) Stop) - (:abstraction (format (:representation Value color) ..stop_separator - (:representation Value start) ..stop_separator - (:representation Value end)))) + (abstraction (format (representation Value color) ..stop_separator + (representation Value start) ..stop_separator + (representation Value end)))) (abstract: .public Hint Text (def: .public hint (-> (Value Length) Hint) - (|>> (:representation Value) (:abstraction Hint))) + (|>> (representation Value) (abstraction Hint))) (def: (with_hint [hint stop]) (-> [(Maybe Hint) Stop] Text) (case hint {.#None} - (:representation Stop stop) + (representation Stop stop) {.#Some hint} - (format (:representation Hint hint) ..value_separator (:representation Stop stop)))))) + (format (representation Hint hint) ..value_separator (representation Stop stop)))))) (type: .public (List/1 a) [a (List a)]) @@ -936,17 +936,17 @@ (def: .public angle (-> Angle Text) - (|>> :representation)) + (|>> representation)) (def: .public (turn value) (-> Rev Angle) - (:abstraction (format (%.rev value) "turn"))) + (abstraction (format (%.rev value) "turn"))) (def: degree_limit Nat 360) (def: .public (degree value) (-> Nat Angle) - (:abstraction (format (%.nat (n.% ..degree_limit value)) "deg"))) + (abstraction (format (%.nat (n.% ..degree_limit value)) "deg"))) (template [<degree> <name>] [(def: .public <name> @@ -963,7 +963,7 @@ [(def: .public (<name> angle start next) (-> Angle Stop (List/1 [(Maybe Hint) Stop]) (Value Image)) (let [[now after] next] - (..apply <function> (list& (:representation Angle angle) + (..apply <function> (list& (representation Angle angle) (with_hint now) (list#each with_hint after)))))] @@ -976,16 +976,16 @@ (def: .public (%% value) (-> Nat (Value Percentage)) - (:abstraction (format (%.nat (n.% percentage_limit value)) "%"))) + (abstraction (format (%.nat (n.% percentage_limit value)) "%"))) (def: .public slice_percent/1 (-> (Value Percentage) (Value Slice)) - (|>> :transmutation)) + (|>> transmutation)) (def: .public (slice_percent/2 horizontal vertical) (-> (Value Percentage) (Value Percentage) (Value Slice)) - (:abstraction (format (:representation horizontal) ..slice_separator - (:representation vertical)))) + (abstraction (format (representation horizontal) ..slice_separator + (representation vertical)))) (template [<input> <pre> <function>+] [(`` (template [<name> <function>] @@ -995,11 +995,11 @@ (~~ (template.spliced <function>+))))] - [Nat (<| :representation ..px n.frac) + [Nat (<| representation ..px n.frac) [[blur "blur"]]] [Nat (<| ..angle ..degree) [[hue_rotate "hue-rotate"]]] - [(Value Percentage) :representation + [(Value Percentage) representation [[brightness "brightness"] [contrast "contrast"] [grayscale "grayscale"] @@ -1020,11 +1020,11 @@ (Maybe (Value Length)) (Maybe (Value Length)) (Value Color) (Value Filter)) - (|> (list (:representation horizontal) - (:representation vertical) - (|> blur (maybe.else ..default_shadow_length) :representation) - (|> spread (maybe.else ..default_shadow_length) :representation) - (:representation color)) + (|> (list (representation horizontal) + (representation vertical) + (|> blur (maybe.else ..default_shadow_length) representation) + (|> spread (maybe.else ..default_shadow_length) representation) + (representation color)) (text.interposed " ") (list) (..apply "drop-shadow"))) @@ -1034,9 +1034,9 @@ (template [<name> <type>] [(def: .public (<name> horizontal vertical) (-> (Value Length) (Value Length) (Value <type>)) - (:abstraction (format (:representation horizontal) - ..length_separator - (:representation vertical))))] + (abstraction (format (representation horizontal) + ..length_separator + (representation vertical))))] [location Location] [fit Fit] @@ -1071,7 +1071,7 @@ (-> Shape (Maybe Extent) (Value Location) Stop (List/1 [(Maybe Hint) Stop]) (Value Image)) - (let [after_extent (format "at " (:representation location)) + (let [after_extent (format "at " (representation location)) with_extent (case extent {.#Some extent} (format (..extent extent) " " after_extent) @@ -1096,14 +1096,14 @@ (let [with_inset (if inset? (list "inset") (list))] - (|> (list& (:representation horizontal) - (:representation vertical) - (|> blur (maybe.else ..default_shadow_length) :representation) - (|> spread (maybe.else ..default_shadow_length) :representation) - (:representation color) + (|> (list& (representation horizontal) + (representation vertical) + (|> blur (maybe.else ..default_shadow_length) representation) + (|> spread (maybe.else ..default_shadow_length) representation) + (representation color) with_inset) (text.interposed " ") - :abstraction))) + abstraction))) (type: .public Rectangle (Record @@ -1115,21 +1115,21 @@ (def: .public (clip rectangle) (-> Rectangle (Value Clip)) (`` (..apply "rect" (list (~~ (template [<side>] - [(:representation (the <side> rectangle))] + [(representation (the <side> rectangle))] [#top] [#right] [#bottom] [#left])))))) (def: .public counter (-> Label (Value Counter)) - (|>> :abstraction)) + (|>> abstraction)) (def: .public current_count (-> (Value Counter) (Value Content)) - (|>> :representation (list) (..apply "counter"))) + (|>> representation (list) (..apply "counter"))) (def: .public text (-> Text (Value Content)) - (|>> %.text :abstraction)) + (|>> %.text abstraction)) (def: .public attribute (-> Label (Value Content)) @@ -1148,7 +1148,7 @@ [monospace "monospace"]] [(def: .public font (-> Text Font) - (|>> %.text :abstraction)) + (|>> %.text abstraction)) (def: .public (font_family options) (-> (List Font) (Value Font)) @@ -1157,57 +1157,57 @@ (|> options (list#each ..font_name) (text.interposed ",") - (:abstraction Value)) + (abstraction Value)) {.#End} ..initial))]) (def: .public font_size (-> (Value Length) (Value Font_Size)) - (|>> :transmutation)) + (|>> transmutation)) (def: .public number (-> Frac (Value Number)) - (|>> %number :abstraction)) + (|>> %number abstraction)) (def: .public grid (-> Label (Value Grid)) - (|>> :abstraction)) + (|>> abstraction)) (def: .public fit_content (-> (Value Length) (Value Grid_Content)) - (|>> :representation (list) (..apply "fit-content"))) + (|>> representation (list) (..apply "fit-content"))) (def: .public (min_max min max) (-> (Value Grid_Content) (Value Grid_Content) (Value Grid_Content)) - (..apply "minmax" (list (:representation min) - (:representation max)))) + (..apply "minmax" (list (representation min) + (representation max)))) (def: .public grid_span (-> Nat (Value Grid_Span)) - (|>> %.nat (format "span ") :abstraction)) + (|>> %.nat (format "span ") abstraction)) (def: grid_column_separator " ") (def: grid_row_separator " ") (def: .public grid_template (-> (List (List (Maybe (Value Grid)))) (Value Grid_Template)) - (let [empty (: (Value Grid) - (:abstraction "."))] + (let [empty (is (Value Grid) + (abstraction "."))] (|>> (list#each (|>> (list#each (|>> (maybe.else empty) - :representation)) + representation)) (text.interposed ..grid_column_separator) (text.enclosed ["'" "'"]))) (text.interposed ..grid_row_separator) - :abstraction))) + abstraction))) (def: .public (resolution dpi) (-> Nat (Value Resolution)) - (:abstraction (format (%.nat dpi) "dpi"))) + (abstraction (format (%.nat dpi) "dpi"))) (def: .public (ratio numerator denominator) (-> Nat Nat (Value Ratio)) - (:abstraction (format (%.nat numerator) "/" (%.nat denominator)))) + (abstraction (format (%.nat numerator) "/" (%.nat denominator)))) (enumeration: Quote Text quote_text @@ -1224,7 +1224,7 @@ [low_double_quote "\201E"]] [(def: .public quote (-> Text Quote) - (|>> :abstraction))]) + (|>> abstraction))]) (def: quote_separator " ") @@ -1233,7 +1233,7 @@ (|> (list left0 right0 left1 right1) (list#each (|>> ..quote_text %.text)) (text.interposed ..quote_separator) - :abstraction)) + abstraction)) (def: .public (matrix_2d [a b] [c d] [tx ty]) (-> [Frac Frac] @@ -1302,24 +1302,24 @@ (def: .public (origin_2d x y) (-> (Value Length) (Value Length) (Value Transform_Origin)) - (:abstraction (format (:representation x) ..origin_separator - (:representation y)))) + (abstraction (format (representation x) ..origin_separator + (representation y)))) (def: .public (origin_3d x y z) (-> (Value Length) (Value Length) (Value Length) (Value Transform_Origin)) - (:abstraction (format (:representation x) ..origin_separator - (:representation y) ..origin_separator - (:representation z)))) + (abstraction (format (representation x) ..origin_separator + (representation y) ..origin_separator + (representation z)))) (def: .public vertical_align (-> (Value Length) (Value Vertical_Align)) - (|>> :transmutation)) + (|>> transmutation)) (def: .public (z_index index) (-> Int (Value Z_Index)) - (:abstraction (if (i.< +0 index) - (%.int index) - (%.nat (.nat index))))) + (abstraction (if (i.< +0 index) + (%.int index) + (%.nat (.nat index))))) (multi: multi_image Image ",") (multi: multi_shadow Shadow ",") @@ -1331,11 +1331,11 @@ (.All (_ kind) (-> (Value <parameter>) (Value (Numeric kind)) (Value (Numeric kind)))) - (|> (format (:representation subject) + (|> (format (representation subject) (template.text [" " <name> " "]) - (:representation parameter)) + (representation parameter)) (text.enclosed ["calc(" ")"]) - :abstraction))] + abstraction))] [+ (Numeric kind)] [- (Numeric kind)] diff --git a/stdlib/source/library/lux/data/format/html.lux b/stdlib/source/library/lux/data/format/html.lux index b6021695d..96de4515b 100644 --- a/stdlib/source/library/lux/data/format/html.lux +++ b/stdlib/source/library/lux/data/format/html.lux @@ -15,7 +15,7 @@ [target ["[0]" js]] [type - abstract] + [abstract {"-" pattern}]] [world [net {"+" URL}]]]] [// @@ -121,21 +121,21 @@ (def: .public html (-> Document Text) - (|>> :representation)) + (|>> representation)) (def: .public (and pre post) (All (_ brand) (-> (HTML brand) (HTML brand) (HTML brand))) - (:abstraction (format (:representation pre) (:representation post)))) + (abstraction (format (representation pre) (representation post)))) (def: .public (comment content node) (All (_ brand) (-> Text (HTML brand) (HTML brand))) - (:abstraction + (abstraction (format (text.enclosed ["<!--" "-->"] content) - (:representation node)))) + (representation node)))) (def: (empty name attributes) (-> Tag Attributes HTML) - (:abstraction + (abstraction (format (..open name attributes) (..close name)))) @@ -143,18 +143,18 @@ (-> Tag Attributes HTML) (|> attributes (..open tag) - :abstraction)) + abstraction)) (def: (tag name attributes content) (-> Tag Attributes (HTML Any) HTML) - (:abstraction + (abstraction (format (..open name attributes) - (:representation content) + (representation content) (..close name)))) (def: (raw tag attributes content) (-> Text Attributes Text HTML) - (:abstraction + (abstraction (format (..open tag attributes) content (..close tag)))) @@ -197,7 +197,7 @@ (def: .public text (-> Text Content) (|>> ..safe - :abstraction)) + abstraction)) (.template [<tag> <alias> <name>] [(def: .public <name> @@ -550,7 +550,7 @@ content {.#Some caption} - (..and (:as HTML caption) + (..and (as HTML caption) content))] (..tag "table" attributes content))) @@ -561,9 +561,9 @@ (let [doc_type <doc_type>] (function (_ head body) (|> (..tag "html" (list) (..and head body)) - :representation + representation (format doc_type) - :abstraction))))] + abstraction))))] [html/5 "<!DOCTYPE html>"] [html/4_01 (format "<!DOCTYPE HTML PUBLIC " text.double_quote "-//W3C//DTD HTML 4.01//EN" text.double_quote " " text.double_quote "http://www.w3.org/TR/html4/strict.dtd" text.double_quote ">")] diff --git a/stdlib/source/library/lux/data/format/json.lux b/stdlib/source/library/lux/data/format/json.lux index d5eafa15d..0a08da9b6 100644 --- a/stdlib/source/library/lux/data/format/json.lux +++ b/stdlib/source/library/lux/data/format/json.lux @@ -123,7 +123,7 @@ code)) (syntax: .public (json [token ..jsonP]) - (in (list (` (: JSON (~ (jsonF token))))))) + (in (list (` (is JSON (~ (jsonF token))))))) (def: .public (fields json) (-> JSON (Try (List String))) diff --git a/stdlib/source/library/lux/data/format/markdown.lux b/stdlib/source/library/lux/data/format/markdown.lux index 02a8de78e..984c023c1 100644 --- a/stdlib/source/library/lux/data/format/markdown.lux +++ b/stdlib/source/library/lux/data/format/markdown.lux @@ -1,15 +1,15 @@ (.using - [library - [lux {"-" and} - [data - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [type - abstract] - [world - [net {"+" URL}]]]]) + [library + [lux {"-" and} + [data + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [type + [abstract {"-" pattern}]] + [world + [net {"+" URL}]]]]) ... https://www.markdownguide.org/basic-syntax/ @@ -39,11 +39,11 @@ (def: .public empty Markdown - (:abstraction "")) + (abstraction "")) (def: .public text (-> Text (Markdown Span)) - (|>> ..safe :abstraction)) + (|>> ..safe abstraction)) (def: blank_line (format text.new_line text.new_line)) @@ -51,7 +51,7 @@ (template [<name> <prefix>] [(def: .public (<name> content) (-> Text (Markdown Block)) - (:abstraction (format <prefix> " " (..safe content) ..blank_line)))] + (abstraction (format <prefix> " " (..safe content) ..blank_line)))] [heading/1 "#"] [heading/2 "##"] @@ -63,22 +63,22 @@ (def: (block content) (-> Text (Markdown Block)) - (:abstraction (format content ..blank_line))) + (abstraction (format content ..blank_line))) (def: .public paragraph (-> (Markdown Span) (Markdown Block)) - (|>> :representation ..block)) + (|>> representation ..block)) (def: .public break (Markdown Span) - (:abstraction (format " " text.new_line))) + (abstraction (format " " text.new_line))) (template [<name> <wrapper>] [(def: .public <name> (-> (Markdown Span) (Markdown Span)) - (|>> :representation + (|>> representation (text.enclosed [<wrapper> <wrapper>]) - :abstraction))] + abstraction))] [bold "**"] [italic "_"] @@ -99,20 +99,20 @@ (def: .public quote (-> (Markdown Block) (Markdown Block)) - (|>> :representation + (|>> representation (..prefix "> ") - :abstraction)) + abstraction)) (def: .public numbered_list (-> (List [(Markdown Span) (Maybe (Markdown Block))]) (Markdown Block)) (|>> list.enumeration (list#each (function (_ [idx [summary detail]]) - (format "1. " (:representation summary) + (format "1. " (representation summary) (case detail {.#Some detail} (|> detail - :representation + representation ..indent (text.enclosed [text.new_line text.new_line]) (format text.new_line)) @@ -126,11 +126,11 @@ (-> (List [(Markdown Span) (Maybe (Markdown Block))]) (Markdown Block)) (|>> (list#each (function (_ [summary detail]) - (format "* " (:representation summary) + (format "* " (representation summary) (case detail {.#Some detail} (|> detail - :representation + representation ..indent (text.enclosed [text.new_line text.new_line]) (format text.new_line)) @@ -143,7 +143,7 @@ ... A snippet of code. (def: .public snippet (-> Text (Markdown Span)) - (|>> (text.enclosed ["`` " " ``"]) :abstraction)) + (|>> (text.enclosed ["`` " " ``"]) abstraction)) ... A (generic) block of code. (def: .public generic_code @@ -163,7 +163,7 @@ (def: .public (image description url) (-> Text URL (Markdown Span)) - (:abstraction (format "![" (..safe description) "](" url ")"))) + (abstraction (format "![" (..safe description) "](" url ")"))) (def: .public horizontal_rule (Markdown Block) @@ -171,7 +171,7 @@ (def: .public (link description url) (-> (Markdown Span) URL (Markdown Span)) - (:abstraction (format "[" (:representation description) "](" url ")"))) + (abstraction (format "[" (representation description) "](" url ")"))) (type: .public Email Text) @@ -179,7 +179,7 @@ (template [<name> <type>] [(def: .public <name> (-> <type> (Markdown Span)) - (|>> (text.enclosed ["<" ">"]) :abstraction))] + (|>> (text.enclosed ["<" ">"]) abstraction))] [url URL] [email Email] @@ -188,7 +188,7 @@ (template [<name> <brand> <infix>] [(def: .public (<name> pre post) (-> (Markdown <brand>) (Markdown <brand>) (Markdown <brand>)) - (:abstraction (format (:representation pre) <infix> (:representation post))))] + (abstraction (format (representation pre) <infix> (representation post))))] [and Span " "] [then Block ""] @@ -196,5 +196,5 @@ (def: .public markdown (All (_ a) (-> (Markdown a) Text)) - (|>> :representation)) + (|>> representation)) ) diff --git a/stdlib/source/library/lux/data/format/tar.lux b/stdlib/source/library/lux/data/format/tar.lux index 567d1a10a..422d11814 100644 --- a/stdlib/source/library/lux/data/format/tar.lux +++ b/stdlib/source/library/lux/data/format/tar.lux @@ -33,7 +33,7 @@ [world ["[0]" file]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) (type: Size Nat) @@ -78,18 +78,18 @@ (def: .public (<in> value) (-> Nat (Try <type>)) (if (n.< <limit> value) - {try.#Success (:abstraction value)} + {try.#Success (abstraction value)} (exception.except <exception> [value]))) (def: .public <out> (-> <type> Nat) - (|>> :representation)) + (|>> representation)) (def: <writer> (Writer <type>) (let [suffix <suffix> padded_size (n.+ (text.size suffix) <size>)] - (|>> :representation + (|>> representation (# n.octal encoded) (..octal_padding <size>) (text.suffix suffix) @@ -99,7 +99,7 @@ (def: <coercion> (-> Nat <type>) (|>> (n.% <limit>) - :abstraction)) + abstraction)) )] [not_a_small_number small_limit ..small_size @@ -161,11 +161,11 @@ (def: from_checksum (-> Checksum Text) - (|>> :representation)) + (|>> representation)) (def: dummy_checksum Checksum - (:abstraction " ")) + (abstraction " ")) (def: checksum_suffix (format ..blank ..null)) @@ -176,7 +176,7 @@ (def: checksum_checksum (|> ..dummy_checksum - :representation + representation (# utf8.codec encoded) ..checksum)) @@ -188,13 +188,13 @@ (# n.octal encoded) (..octal_padding ..small_size) (text.suffix ..checksum_suffix) - :abstraction)) + abstraction)) (def: checksum_writer (Writer Checksum) (let [padded_size (n.+ (text.size ..checksum_suffix) ..small_size)] - (|>> :representation + (|>> representation (# utf8.codec encoded) (format.segment padded_size)))) @@ -207,7 +207,7 @@ value (<>.lifted (# n.octal decoded digits))] (in [value - (:abstraction (format digits ..checksum_suffix))]))) + (abstraction (format digits ..checksum_suffix))]))) ) (def: last_ascii @@ -263,18 +263,18 @@ binary.size (n.> <size>)) (exception.except <exception> [value]) - {try.#Success (:abstraction value)}) + {try.#Success (abstraction value)}) (exception.except ..not_ascii [value]))) (def: .public <out> (-> <type> <representation>) - (|>> :representation)) + (|>> representation)) (def: <writer> (Writer <type>) (let [suffix ..null padded_size (n.+ (text.size suffix) <size>)] - (|>> :representation + (|>> representation (text.suffix suffix) (# utf8.codec encoded) (format.segment padded_size)))) @@ -308,17 +308,17 @@ Text (def: ustar - (:abstraction "ustar ")) + (abstraction "ustar ")) (def: from_magic (-> Magic Text) - (|>> :representation)) + (|>> representation)) (def: magic_writer (Writer Magic) (let [padded_size (n.+ (text.size ..null) ..magic_size)] - (|>> :representation + (|>> representation (# utf8.codec encoded) (format.segment padded_size)))) @@ -331,7 +331,7 @@ _ (<>.assertion (exception.error ..wrong_character [expected end]) (n.= expected end))] (<>.lifted - (# try.monad each (|>> :abstraction) + (# try.monad each (|>> abstraction) (# utf8.codec decoded string))))) ) @@ -396,11 +396,11 @@ (def: link_flag (-> Link_Flag Char) - (|>> :representation)) + (|>> representation)) (def: link_flag_writer (Writer Link_Flag) - (|>> :representation + (|>> representation format.bits/8)) (with_expansions [<options> (as_is [0 old_normal] @@ -415,7 +415,7 @@ (template [<flag> <name>] [(def: <name> Link_Flag - (:abstraction <flag>))] + (abstraction <flag>))] <options> ) @@ -444,17 +444,17 @@ (def: .public mode (-> Mode Nat) - (|>> :representation)) + (|>> representation)) (def: .public (and left right) (-> Mode Mode Mode) - (:abstraction - (i64.or (:representation left) - (:representation right)))) + (abstraction + (i64.or (representation left) + (representation right)))) (def: mode_writer (Writer Mode) - (|>> :representation + (|>> representation ..small try.trusted ..small_writer)) @@ -483,7 +483,7 @@ (template [<code> <name>] [(def: .public <name> Mode - (:abstraction (number.oct <code>)))] + (abstraction (number.oct <code>)))] <options> ) @@ -514,11 +514,11 @@ (Parser Mode) (do [! <>.monad] [value (# ! each ..from_small ..small_parser)] - (if (n.> (:representation ..maximum_mode) + (if (n.> (representation ..maximum_mode) value) (<>.lifted (exception.except ..invalid_mode [value])) - (in (:abstraction value)))))) + (in (abstraction value)))))) ) (def: maximum_content_size @@ -534,15 +534,15 @@ (-> Binary (Try Content)) (do try.monad [size (..big (binary.size content))] - (in (:abstraction [size content])))) + (in (abstraction [size content])))) (def: from_content (-> Content [Big Binary]) - (|>> :representation)) + (|>> representation)) (def: .public data (-> Content Binary) - (|>> :representation product.right)) + (|>> representation product.right)) ) (type: .public ID diff --git a/stdlib/source/library/lux/data/format/xml.lux b/stdlib/source/library/lux/data/format/xml.lux index 825daeac3..2459936a2 100644 --- a/stdlib/source/library/lux/data/format/xml.lux +++ b/stdlib/source/library/lux/data/format/xml.lux @@ -220,9 +220,9 @@ (def: xml_header Text - (let [quote (: (-> Text Text) - (function (_ value) - ($_ text#composite text.double_quote value text.double_quote)))] + (let [quote (is (-> Text Text) + (function (_ value) + ($_ text#composite text.double_quote value text.double_quote)))] ($_ text#composite "<?xml" " version=" (quote "1.0") @@ -233,13 +233,13 @@ (Codec Text XML) (def: encoded - (let [attributes (: (-> Attrs Text) - (function (_ attrs) - (|> attrs - dictionary.entries - (list#each (function (_ [key value]) - ($_ text#composite (..attribute key) "=" text.double_quote (sanitize_value value) text.double_quote))) - (text.interposed " "))))] + (let [attributes (is (-> Attrs Text) + (function (_ attrs) + (|> attrs + dictionary.entries + (list#each (function (_ [key value]) + ($_ text#composite (..attribute key) "=" text.double_quote (sanitize_value value) text.double_quote))) + (text.interposed " "))))] (function (_ input) ($_ text#composite ..xml_header text.new_line diff --git a/stdlib/source/library/lux/data/text.lux b/stdlib/source/library/lux/data/text.lux index 29d2d0ca8..922f1da3c 100644 --- a/stdlib/source/library/lux/data/text.lux +++ b/stdlib/source/library/lux/data/text.lux @@ -69,8 +69,8 @@ (def: .public (last_index part text) (-> Text Text (Maybe Nat)) (loop [offset 0 - output (: (Maybe Nat) - {.#None})] + output (is (Maybe Nat) + {.#None})] (let [output' ("lux text index" offset part text)] (case output' {.#None} @@ -165,7 +165,7 @@ (def: .public (all_split_by token sample) (-> Text Text (List Text)) (loop [input sample - output (: (List Text) (list))] + output (is (List Text) (list))] (case (..split_by token input) {.#Some [pre post]} (|> output @@ -221,34 +221,34 @@ {.#None} ("lux text concat" left right)))] (for @.old - (:as Text - ("jvm invokevirtual:java.lang.String:replace:java.lang.CharSequence,java.lang.CharSequence" - (:as (Primitive "java.lang.String") template) - (:as (Primitive "java.lang.CharSequence") pattern) - (:as (Primitive "java.lang.CharSequence") replacement))) + (as Text + ("jvm invokevirtual:java.lang.String:replace:java.lang.CharSequence,java.lang.CharSequence" + (as (Primitive "java.lang.String") template) + (as (Primitive "java.lang.CharSequence") pattern) + (as (Primitive "java.lang.CharSequence") replacement))) @.jvm - (:as Text - ("jvm member invoke virtual" [] "java.lang.String" "replace" [] - (:as (Primitive "java.lang.String") template) - ["Ljava/lang/CharSequence;" (:as (Primitive "java.lang.CharSequence") pattern)] - ["Ljava/lang/CharSequence;" (:as (Primitive "java.lang.CharSequence") replacement)])) + (as Text + ("jvm member invoke virtual" [] "java.lang.String" "replace" [] + (as (Primitive "java.lang.String") template) + ["Ljava/lang/CharSequence;" (as (Primitive "java.lang.CharSequence") pattern)] + ["Ljava/lang/CharSequence;" (as (Primitive "java.lang.CharSequence") replacement)])) @.js ... TODO: Remove this when Nashorn is no longer being used. (..if_nashorn <default> - (:as Text - ("js object do" "replaceAll" template [pattern replacement]))) + (as Text + ("js object do" "replaceAll" template [pattern replacement]))) @.python - (:as Text - ("python object do" "replace" template [pattern replacement])) + (as Text + ("python object do" "replace" template [pattern replacement])) ... TODO @.lua @.ruby - (:as Text - ("ruby object do" "gsub" template [pattern replacement])) + (as Text + ("ruby object do" "gsub" template [pattern replacement])) @.php - (:as Text - ("php apply" (:expected ("php constant" "str_replace")) - pattern replacement template)) + (as Text + ("php apply" (as_expected ("php constant" "str_replace")) + pattern replacement template)) ... TODO @.scheme ... TODO @.common_lisp ... TODO @.r @@ -286,19 +286,19 @@ (def: (hash input) (for @.old (|> input - (: (Primitive "java.lang.String")) + (is (Primitive "java.lang.String")) "jvm invokevirtual:java.lang.String:hashCode:" "jvm convert int-to-long" - (:as Nat)) + (as Nat)) @.jvm (|> input - (:as (Primitive "java.lang.String")) + (as (Primitive "java.lang.String")) ("jvm member invoke virtual" [] "java.lang.String" "hashCode" []) "jvm conversion int-to-long" "jvm object cast" - (: (Primitive "java.lang.Long")) - (:as Nat)) + (is (Primitive "java.lang.Long")) + (as Nat)) ... Platform-independent default. (let [length ("lux text size" input)] (loop [index 0 @@ -355,45 +355,45 @@ (def: .public (lower_cased value) (-> Text Text) (for @.old - (:as Text - ("jvm invokevirtual:java.lang.String:toLowerCase:" - (:as (Primitive "java.lang.String") value))) + (as Text + ("jvm invokevirtual:java.lang.String:toLowerCase:" + (as (Primitive "java.lang.String") value))) @.jvm - (:as Text - ("jvm member invoke virtual" [] "java.lang.String" "toLowerCase" [] - (:as (Primitive "java.lang.String") value))) + (as Text + ("jvm member invoke virtual" [] "java.lang.String" "toLowerCase" [] + (as (Primitive "java.lang.String") value))) @.js - (:as Text - ("js object do" "toLowerCase" value [])) + (as Text + ("js object do" "toLowerCase" value [])) @.python - (:as Text - ("python object do" "lower" value [])) + (as Text + ("python object do" "lower" value [])) @.lua - (:as Text - ("lua apply" ("lua constant" "string.lower") [value])) + (as Text + ("lua apply" ("lua constant" "string.lower") [value])) @.ruby - (:as Text - ("ruby object do" "downcase" value [])))) + (as Text + ("ruby object do" "downcase" value [])))) (def: .public (upper_cased value) (-> Text Text) (for @.old - (:as Text - ("jvm invokevirtual:java.lang.String:toUpperCase:" - (:as (Primitive "java.lang.String") value))) + (as Text + ("jvm invokevirtual:java.lang.String:toUpperCase:" + (as (Primitive "java.lang.String") value))) @.jvm - (:as Text - ("jvm member invoke virtual" [] "java.lang.String" "toUpperCase" [] - (:as (Primitive "java.lang.String") value))) + (as Text + ("jvm member invoke virtual" [] "java.lang.String" "toUpperCase" [] + (as (Primitive "java.lang.String") value))) @.js - (:as Text - ("js object do" "toUpperCase" value [])) + (as Text + ("js object do" "toUpperCase" value [])) @.python - (:as Text - ("python object do" "upper" value [])) + (as Text + ("python object do" "upper" value [])) @.lua - (:as Text - ("lua apply" ("lua constant" "string.upper") [value])) + (as Text + ("lua apply" ("lua constant" "string.upper") [value])) @.ruby - (:as Text - ("ruby object do" "upcase" value [])))) + (as Text + ("ruby object do" "upcase" value [])))) diff --git a/stdlib/source/library/lux/data/text/buffer.lux b/stdlib/source/library/lux/data/text/buffer.lux index 98526e286..eb1cecf59 100644 --- a/stdlib/source/library/lux/data/text/buffer.lux +++ b/stdlib/source/library/lux/data/text/buffer.lux @@ -16,7 +16,7 @@ [number ["n" nat]]] [type - abstract]]] + [abstract {"-" pattern}]]]] ["[0]" //]) (with_expansions [<jvm> (as_is (import: java/lang/CharSequence @@ -58,78 +58,78 @@ (def: .public empty Buffer - (:abstraction (with_expansions [<jvm> [0 function.identity]] - (for @.old <jvm> - @.jvm <jvm> - @.js [0 function.identity] - @.lua [0 function.identity] - ... default - sequence.empty)))) + (abstraction (with_expansions [<jvm> [0 function.identity]] + (for @.old <jvm> + @.jvm <jvm> + @.js [0 function.identity] + @.lua [0 function.identity] + ... default + sequence.empty)))) (def: .public (then chunk buffer) (-> Text Buffer Buffer) - (with_expansions [<jvm> (let [[capacity transform] (:representation buffer) - then! (: (-> Text java/lang/StringBuilder java/lang/StringBuilder) - (function (_ chunk builder) - (exec - (java/lang/Appendable::append (:as java/lang/CharSequence chunk) - builder) - builder)))] - (:abstraction [(n.+ (//.size chunk) capacity) - (|>> transform (then! chunk))]))] + (with_expansions [<jvm> (let [[capacity transform] (representation buffer) + then! (is (-> Text java/lang/StringBuilder java/lang/StringBuilder) + (function (_ chunk builder) + (exec + (java/lang/Appendable::append (as java/lang/CharSequence chunk) + builder) + builder)))] + (abstraction [(n.+ (//.size chunk) capacity) + (|>> transform (then! chunk))]))] (for @.old <jvm> @.jvm <jvm> - @.js (let [[capacity transform] (:representation buffer) - then! (: (-> (JS_Array Text) (JS_Array Text)) - (function (_ array) - (exec - (JS_Array::push chunk array) - array)))] - (:abstraction [(n.+ (//.size chunk) capacity) - (|>> transform then!)])) - @.lua (let [[capacity transform] (:representation buffer) - then! (: (-> (array.Array Text) (array.Array Text)) + @.js (let [[capacity transform] (representation buffer) + then! (is (-> (JS_Array Text) (JS_Array Text)) (function (_ array) (exec - (table/insert array chunk) + (JS_Array::push chunk array) array)))] - (:abstraction [(n.+ (//.size chunk) capacity) - (|>> transform then!)])) + (abstraction [(n.+ (//.size chunk) capacity) + (|>> transform then!)])) + @.lua (let [[capacity transform] (representation buffer) + then! (is (-> (array.Array Text) (array.Array Text)) + (function (_ array) + (exec + (table/insert array chunk) + array)))] + (abstraction [(n.+ (//.size chunk) capacity) + (|>> transform then!)])) ... default - (|> buffer :representation (sequence.suffix chunk) :abstraction)))) + (|> buffer representation (sequence.suffix chunk) abstraction)))) (def: .public size (-> Buffer Nat) - (with_expansions [<jvm> (|>> :representation product.left)] + (with_expansions [<jvm> (|>> representation product.left)] (for @.old <jvm> @.jvm <jvm> @.js <jvm> @.lua <jvm> ... default - (|>> :representation + (|>> representation (sequence#mix (function (_ chunk total) (n.+ (//.size chunk) total)) 0))))) (def: .public (text buffer) (-> Buffer Text) - (with_expansions [<jvm> (let [[capacity transform] (:representation buffer)] + (with_expansions [<jvm> (let [[capacity transform] (representation buffer)] (|> (java/lang/StringBuilder::new (ffi.as_int (.int capacity))) transform java/lang/StringBuilder::toString ffi.of_string))] (for @.old <jvm> @.jvm <jvm> - @.js (let [[capacity transform] (:representation buffer)] + @.js (let [[capacity transform] (representation buffer)] (|> (array.empty 0) - (:as (JS_Array Text)) + (as (JS_Array Text)) transform (JS_Array::join ""))) - @.lua (let [[capacity transform] (:representation buffer)] + @.lua (let [[capacity transform] (representation buffer)] (table/concat (transform (array.empty 0)) "")) ... default (sequence#mix (function (_ chunk total) (format total chunk)) "" - (:representation buffer))))) + (representation buffer))))) )) diff --git a/stdlib/source/library/lux/data/text/encoding.lux b/stdlib/source/library/lux/data/text/encoding.lux index e28dd31f1..10a29ed5c 100644 --- a/stdlib/source/library/lux/data/text/encoding.lux +++ b/stdlib/source/library/lux/data/text/encoding.lux @@ -1,10 +1,10 @@ (.using - [library - [lux "*" - [macro - ["[0]" template]] - [type - abstract]]]) + [library + [lux "*" + [macro + ["[0]" template]] + [type + [abstract {"-" pattern}]]]]) ... https://en.wikipedia.org/wiki/Character_encoding#Common_character_encodings (abstract: .public Encoding @@ -13,7 +13,7 @@ (template [<name> <encoding>] [(`` (def: .public <name> Encoding - (:abstraction <encoding>)))] + (abstraction <encoding>)))] [ascii "ASCII"] @@ -162,5 +162,5 @@ (def: .public name (-> Encoding Text) - (|>> :representation)) + (|>> representation)) ) diff --git a/stdlib/source/library/lux/data/text/encoding/utf8.lux b/stdlib/source/library/lux/data/text/encoding/utf8.lux index a1627c8d2..e618307b4 100644 --- a/stdlib/source/library/lux/data/text/encoding/utf8.lux +++ b/stdlib/source/library/lux/data/text/encoding/utf8.lux @@ -75,13 +75,13 @@ @.js (cond ffi.on_nashorn? - (:as Binary ("js object do" "getBytes" value ["utf8"])) + (as Binary ("js object do" "getBytes" value ["utf8"])) ffi.on_node_js? (|> (Buffer::from|encoded value "utf8") ... This coercion is valid as per NodeJS's documentation: ... https://nodejs.org/api/buffer.html#buffer_buffers_and_typedarrays - (:as Uint8Array)) + (as Uint8Array)) ... On the browser (|> (TextEncoder::new (//.name //.utf_8)) @@ -89,14 +89,14 @@ ) @.python - (:as Binary ("python apply" (:expected ("python constant" "bytearray")) [value "utf-8"])) + (as Binary ("python apply" (as_expected ("python constant" "bytearray")) [value "utf-8"])) @.lua ("lua utf8 encode" value) @.ruby (|> value - (:as String) + (as String) (String::encode "UTF-8") (String::bytes)) @@ -104,7 +104,7 @@ (|> (..unpack [..php_byte_array_format value]) ..array_values ("php object new" "ArrayObject") - (:as Binary)) + (as Binary)) @.scheme (..string->utf8 value))) @@ -118,7 +118,7 @@ @.js (cond ffi.on_nashorn? (|> ("js object new" ("js constant" "java.lang.String") [value "utf8"]) - (:as Text) + (as Text) {try.#Success}) ffi.on_node_js? @@ -132,16 +132,16 @@ {try.#Success})) @.python - (try (:as Text ("python object do" "decode" (:expected value) ["utf-8"]))) + (try (as Text ("python object do" "decode" (as_expected value) ["utf-8"]))) @.lua {try.#Success ("lua utf8 decode" value)} @.ruby (|> value - (:as Array) + (as Array) (Array::pack "C*") - (:as String) + (as String) (String::force_encoding "UTF-8") {try.#Success}) diff --git a/stdlib/source/library/lux/data/text/regex.lux b/stdlib/source/library/lux/data/text/regex.lux index 0e048bdcd..3ae94415b 100644 --- a/stdlib/source/library/lux/data/text/regex.lux +++ b/stdlib/source/library/lux/data/text/regex.lux @@ -81,7 +81,7 @@ (-> Text (Parser Code)) (do <>.monad [symbol (<text>.enclosed ["\@<" ">"] (symbol^ current_module))] - (in (` (: ((~! <text>.Parser) Text) (~ (code.symbol symbol))))))) + (in (` (is ((~! <text>.Parser) Text) (~ (code.symbol symbol))))))) (def: re_range^ (Parser Code) @@ -286,38 +286,38 @@ (re_scoped^ current_module))) .let [g!total (code.symbol ["" "0total"]) g!temp (code.symbol ["" "0temp"]) - [_ names steps] (list#mix (: (-> (Either Code [Re_Group Code]) - [Nat (List Code) (List (List Code))] - [Nat (List Code) (List (List Code))]) - (function (_ part [idx names steps]) - (case part - (^.or {.#Left complex} - {.#Right [{#Non_Capturing} complex]}) - [idx - names - (list& (list g!temp complex - (` .let) (` [(~ g!total) (# (~! //.monoid) (~' composite) (~ g!total) (~ g!temp))])) - steps)] - - {.#Right [{#Capturing [?name num_captures]} scoped]} - (let [[idx! name!] (case ?name - {.#Some _name} - [idx (code.symbol ["" _name])] - - {.#None} - [(++ idx) (code.symbol ["" (n#encoded idx)])]) - access (if (n.> 0 num_captures) - (` ((~! product.left) (~ name!))) - name!)] - [idx! - (list& name! names) - (list& (list name! scoped - (` .let) (` [(~ g!total) (# (~! //.monoid) (~' composite) (~ g!total) (~ access))])) - steps)]) - ))) + [_ names steps] (list#mix (is (-> (Either Code [Re_Group Code]) + [Nat (List Code) (List (List Code))] + [Nat (List Code) (List (List Code))]) + (function (_ part [idx names steps]) + (case part + (^.or {.#Left complex} + {.#Right [{#Non_Capturing} complex]}) + [idx + names + (list& (list g!temp complex + (` .let) (` [(~ g!total) (# (~! //.monoid) (~' composite) (~ g!total) (~ g!temp))])) + steps)] + + {.#Right [{#Capturing [?name num_captures]} scoped]} + (let [[idx! name!] (case ?name + {.#Some _name} + [idx (code.symbol ["" _name])] + + {.#None} + [(++ idx) (code.symbol ["" (n#encoded idx)])]) + access (if (n.> 0 num_captures) + (` ((~! product.left) (~ name!))) + name!)] + [idx! + (list& name! names) + (list& (list name! scoped + (` .let) (` [(~ g!total) (# (~! //.monoid) (~' composite) (~ g!total) (~ access))])) + steps)]) + ))) [0 - (: (List Code) (list)) - (: (List (List Code)) (list))] + (is (List Code) (list)) + (is (List (List Code)) (list))] parts)]] (in [(if capturing? (list.size names) diff --git a/stdlib/source/library/lux/data/text/unicode/block.lux b/stdlib/source/library/lux/data/text/unicode/block.lux index feab490e3..d0dec884f 100644 --- a/stdlib/source/library/lux/data/text/unicode/block.lux +++ b/stdlib/source/library/lux/data/text/unicode/block.lux @@ -11,7 +11,7 @@ ["n" nat ("[1]#[0]" interval)] ["[0]" i64]]] [type - abstract]]] + [abstract {"-" pattern}]]]] [/// {"+" Char}]) (abstract: .public Block @@ -21,13 +21,13 @@ (Monoid Block) (def: identity - (:abstraction + (abstraction (interval.between n.enum n#top n#bottom))) (def: (composite left right) - (let [left (:representation left) - right (:representation right)] - (:abstraction + (let [left (representation left) + right (representation right)] + (abstraction (interval.between n.enum (n.min (# left bottom) (# right bottom)) @@ -36,12 +36,12 @@ (def: .public (block start additional) (-> Char Nat Block) - (:abstraction (interval.between n.enum start (n.+ additional start)))) + (abstraction (interval.between n.enum start (n.+ additional start)))) (template [<name> <slot>] [(def: .public <name> (-> Block Char) - (|>> :representation (the <slot>)))] + (|>> representation (the <slot>)))] [start interval.bottom] [end interval.top] @@ -49,13 +49,13 @@ (def: .public (size block) (-> Block Nat) - (let [start (the interval.bottom (:representation block)) - end (the interval.top (:representation block))] + (let [start (the interval.bottom (representation block)) + end (the interval.top (representation block))] (|> end (n.- start) ++))) (def: .public (within? block char) (All (_ a) (-> Block Char Bit)) - (interval.within? (:representation block) char)) + (interval.within? (representation block) char)) ) (implementation: .public equivalence diff --git a/stdlib/source/library/lux/data/text/unicode/set.lux b/stdlib/source/library/lux/data/text/unicode/set.lux index b6b1e06b2..89359273b 100644 --- a/stdlib/source/library/lux/data/text/unicode/set.lux +++ b/stdlib/source/library/lux/data/text/unicode/set.lux @@ -1,51 +1,51 @@ (.using - [library - [lux "*" - [abstract - [equivalence {"+" Equivalence}]] - [data - [collection - ["[0]" list ("[1]#[0]" mix functor)] - ["[0]" set ("[1]#[0]" equivalence)] - ["[0]" tree "_" - ["[1]" finger {"+" Tree}]]]] - [type {"+" :by_example} - abstract]]] - ["[0]" / "_" - ["/[1]" // "_" - [// {"+" Char}] - ["[1][0]" block {"+" Block}]]]) + [library + [lux "*" + [abstract + [equivalence {"+" Equivalence}]] + [data + [collection + ["[0]" list ("[1]#[0]" mix functor)] + ["[0]" set ("[1]#[0]" equivalence)] + ["[0]" tree "_" + ["[1]" finger {"+" Tree}]]]] + [type {"+" by_example} + [abstract {"-" pattern}]]]] + ["[0]" / "_" + ["/[1]" // "_" + [// {"+" Char}] + ["[1][0]" block {"+" Block}]]]) (def: builder (tree.builder //block.monoid)) (def: :@: - (:by_example [@] - (tree.Builder @ Block) - ..builder - - @)) + (by_example [@] + (tree.Builder @ Block) + ..builder + + @)) (abstract: .public Set (Tree :@: Block []) (def: .public (composite left right) (-> Set Set Set) - (:abstraction + (abstraction (# builder branch - (:representation left) - (:representation right)))) + (representation left) + (representation right)))) (def: (singleton block) (-> Block Set) - (:abstraction + (abstraction (# builder leaf block []))) (def: .public (set [head tail]) (-> [Block (List Block)] Set) - (list#mix (: (-> Block Set Set) - (function (_ block set) - (..composite (..singleton block) set))) + (list#mix (is (-> Block Set Set) + (function (_ block set) + (..composite (..singleton block) set))) (..singleton head) tail)) @@ -202,19 +202,19 @@ (def: .public start (-> Set Char) - (|>> :representation + (|>> representation tree.tag //block.start)) (def: .public end (-> Set Char) - (|>> :representation + (|>> representation tree.tag //block.end)) (def: .public (member? set character) (-> Set Char Bit) - (loop [tree (:representation set)] + (loop [tree (representation set)] (if (//block.within? (tree.tag tree) character) (case (tree.root tree) {0 #0 _} @@ -229,8 +229,8 @@ (Equivalence Set) (def: (= reference subject) - (set#= (set.of_list //block.hash (tree.tags (:representation reference))) - (set.of_list //block.hash (tree.tags (:representation subject)))))) + (set#= (set.of_list //block.hash (tree.tags (representation reference))) + (set.of_list //block.hash (tree.tags (representation subject)))))) ) (template [<name> <blocks>] diff --git a/stdlib/source/library/lux/debug.lux b/stdlib/source/library/lux/debug.lux index d4665f058..987a25120 100644 --- a/stdlib/source/library/lux/debug.lux +++ b/stdlib/source/library/lux/debug.lux @@ -136,7 +136,7 @@ (-> Inspector Inspector) (with_expansions [<adaption> (for @.lua (~~ (as_is ..tuple_array)) (~~ (as_is)))] - (`` (|>> (:as (array.Array Any)) + (`` (|>> (as (array.Array Any)) <adaption> (array.list {.#None}) (list#each inspection) @@ -145,7 +145,7 @@ (def: .public (inspection value) Inspector - (with_expansions [<jvm> (let [object (:as java/lang/Object value)] + (with_expansions [<jvm> (let [object (as java/lang/Object value)] (`` (<| (~~ (template [<class> <processing>] [(case (ffi.check <class> object) {.#Some value} @@ -160,7 +160,7 @@ )) (case (ffi.check [java/lang/Object] object) {.#Some value} - (let [value (:as (array.Array java/lang/Object) value)] + (let [value (as (array.Array java/lang/Object) value)] (case (array.read! 0 value) (^.multi {.#Some tag} [(ffi.check java/lang/Integer tag) @@ -187,9 +187,9 @@ (^.template [<type_of> <then>] [<type_of> (`` (|> value (~~ (template.spliced <then>))))]) - (["boolean" [(:as .Bit) %.bit]] - ["number" [(:as .Frac) %.frac]] - ["string" [(:as .Text) %.text]] + (["boolean" [(as .Bit) %.bit]] + ["number" [(as .Frac) %.frac]] + ["string" [(as .Text) %.text]] ["undefined" [JSON::stringify]]) "object" @@ -206,7 +206,7 @@ (not (or ("js object undefined?" ("js object get" "_lux_low" value)) ("js object undefined?" ("js object get" "_lux_high" value)))) - (|> value (:as .Int) %.int) + (|> value (as .Int) %.int) (Array::isArray value) (tuple_inspection inspection value) @@ -222,17 +222,17 @@ (^.template [<type_of> <class_of> <then>] [(^.or <type_of> <class_of>) (`` (|> value (~~ (template.spliced <then>))))]) - (["<type 'bool'>" "<class 'bool'>" [(:as .Bit) %.bit]] - ["<type 'int'>" "<class 'int'>" [(:as .Int) %.int]] - ["<type 'float'>" "<class 'float'>" [(:as .Frac) %.frac]] - ["<type 'str'>" "<class 'str'>" [(:as .Text) %.text]] - ["<type 'unicode'>" "<class 'unicode'>" [(:as .Text) %.text]]) + (["<type 'bool'>" "<class 'bool'>" [(as .Bit) %.bit]] + ["<type 'int'>" "<class 'int'>" [(as .Int) %.int]] + ["<type 'float'>" "<class 'float'>" [(as .Frac) %.frac]] + ["<type 'str'>" "<class 'str'>" [(as .Text) %.text]] + ["<type 'unicode'>" "<class 'unicode'>" [(as .Text) %.text]]) (^.or "<type 'list'>" "<class 'list'>") (tuple_inspection inspection value) (^.or "<type 'tuple'>" "<class 'tuple'>") - (let [variant (:as (array.Array Any) value)] + (let [variant (as (array.Array Any) value)] (case (array.size variant) 3 (let [variant_tag ("python array read" 0 variant) variant_flag ("python array read" 1 variant) @@ -240,7 +240,7 @@ (if (or ("python object none?" variant_tag) ("python object none?" variant_value)) (..str value) - (|> (%.format (|> variant_tag (:as .Nat) %.nat) + (|> (%.format (|> variant_tag (as .Nat) %.nat) " " (|> variant_flag "python object none?" not %.bit) " " (inspection variant_value)) (text.enclosed ["{" "}"])))) @@ -254,14 +254,14 @@ (^.template [<type_of> <then>] [<type_of> (`` (|> value (~~ (template.spliced <then>))))]) - (["boolean" [(:as .Bit) %.bit]] - ["string" [(:as .Text) %.text]] + (["boolean" [(as .Bit) %.bit]] + ["string" [(as .Text) %.text]] ["nil" [(pipe.new "nil" [])]]) "number" (case (math::type value) - {.#Some "integer"} (|> value (:as .Int) %.int) - {.#Some "float"} (|> value (:as .Frac) %.frac) + {.#Some "integer"} (|> value (as .Int) %.int) + {.#Some "float"} (|> value (as .Frac) %.frac) _ (..tostring value)) @@ -273,7 +273,7 @@ (if (or ("lua object nil?" variant_tag) ("lua object nil?" variant_value)) (tuple_inspection inspection value) - (|> (%.format (|> variant_tag (:as .Nat) %.nat) + (|> (%.format (|> variant_tag (as .Nat) %.nat) " " (%.bit (not ("lua object nil?" variant_flag))) " " (inspection variant_value)) (text.enclosed ["{" "}"])))) @@ -284,17 +284,17 @@ @.ruby (template.let [(class_of <literal>) [(|> <literal> - (:as ..Object) + (as ..Object) Object::class)] (to_s <object>) [(|> <object> - (:as ..Object) + (as ..Object) Object::to_s)]] (let [value_class (class_of value)] (`` (cond (~~ (template [<literal> <type> <format>] [(same? (class_of <literal>) value_class) - (|> value (:as <type>) <format>)] + (|> value (as <type>) <format>)] [#0 Bit %.bit] [#1 Bit %.bit] @@ -311,7 +311,7 @@ (if (or ("ruby object nil?" variant_tag) ("ruby object nil?" variant_value)) (tuple_inspection inspection value) - (|> (%.format (|> variant_tag (:as .Nat) %.nat) + (|> (%.format (|> variant_tag (as .Nat) %.nat) " " (%.bit (not ("ruby object nil?" variant_flag))) " " (inspection variant_value)) (text.enclosed ["{" "}"])))) @@ -327,10 +327,10 @@ (^.template [<type_of> <then>] [<type_of> (`` (|> value (~~ (template.spliced <then>))))]) - (["boolean" [(:as .Bit) %.bit]] - ["integer" [(:as .Int) %.int]] - ["double" [(:as .Frac) %.frac]] - ["string" [(:as .Text) %.text]] + (["boolean" [(as .Bit) %.bit]] + ["integer" [(as .Int) %.int]] + ["double" [(as .Frac) %.frac]] + ["string" [(as .Text) %.text]] ["NULL" [(pipe.new "null" [])]] ["array" [(tuple_inspection inspection)]]) @@ -341,7 +341,7 @@ (if (or ("php object null?" variant_tag) ("php object null?" variant_value)) (..strval value) - (|> (%.format (|> variant_tag (:as .Nat) %.nat) + (|> (%.format (|> variant_tag (as .Nat) %.nat) " " (%.bit (not ("php object null?" variant_flag))) " " (inspection variant_value)) (text.enclosed ["{" "}"])))) @@ -354,10 +354,10 @@ [(<when> value) (`` (|> value (~~ (template.spliced <then>))))] - [..boolean? [(:as .Bit) %.bit]] - [..integer? [(:as .Int) %.int]] - [..real? [(:as .Frac) %.frac]] - [..string? [(:as .Text) %.text]] + [..boolean? [(as .Bit) %.bit]] + [..integer? [(as .Int) %.int]] + [..real? [(as .Frac) %.frac]] + [..string? [(as .Text) %.text]] ["scheme object nil?" [(pipe.new "()" [])]] [..vector? [(tuple_inspection inspection)]])) @@ -365,11 +365,11 @@ (let [variant_tag (..car value) variant_rest (..cdr value)] (if (and (..integer? variant_tag) - (i.> +0 (:as Int variant_tag)) + (i.> +0 (as Int variant_tag)) (..pair? variant_rest)) (let [variant_flag (..car variant_rest) variant_value (..cdr variant_rest)] - (|> (%.format (|> variant_tag (:as .Nat) %.nat) + (|> (%.format (|> variant_tag (as .Nat) %.nat) " " (%.bit (not ("scheme object nil?" variant_flag))) " " (inspection variant_value)) (text.enclosed ["{" "}"]))) @@ -397,7 +397,7 @@ (~~ (template [<type> <formatter>] [(do <>.monad [_ (<type>.sub <type>)] - (in (|>> (:as <type>) <formatter>)))] + (in (|>> (as <type>) <formatter>)))] [Bit %.bit] [Nat %.nat] @@ -413,7 +413,7 @@ (~~ (template [<type> <formatter>] [(do <>.monad [_ (<type>.sub <type>)] - (in (|>> (:as <type>) <formatter>)))] + (in (|>> (as <type>) <formatter>)))] [Ratio %.ratio] [Symbol %.symbol] @@ -434,12 +434,12 @@ (do <>.monad [[_ elemT] (<type>.applied (<>.and (<type>.exactly List) <type>.any)) elemR (<type>.local (list elemT) representation)] - (in (|>> (:as (List Any)) (%.list elemR)))) + (in (|>> (as (List Any)) (%.list elemR)))) (do <>.monad [[_ elemT] (<type>.applied (<>.and (<type>.exactly Maybe) <type>.any)) elemR (<type>.local (list elemT) representation)] - (in (|>> (:as (Maybe Any)) + (in (|>> (as (Maybe Any)) (%.maybe elemR))))))) (def: (variant_representation representation) @@ -452,7 +452,7 @@ variantV variantV] (case representations {.#Item leftR {.#Item rightR extraR+}} - (case (:as (Or Any Any) variantV) + (case (as (Or Any Any) variantV) {.#Left left} [lefts #0 (leftR left)] @@ -483,7 +483,7 @@ (lastR tupleV) {.#Item headR tailR} - (let [[leftV rightV] (:as [Any Any] tupleV)] + (let [[leftV rightV] (as [Any Any] tupleV)] (%.format (headR leftV) " " (again tailR rightV)))))] (%.format "[" tuple_body "]")))))) @@ -538,7 +538,7 @@ "Location" (%.location location) "Type" (%.type type))) -(syntax: .public (:hole []) +(syntax: .public (hole []) (do meta.monad [location meta.location expectedT meta.expected_type] @@ -558,10 +558,10 @@ (exception.report "Name" (%.text name))) -(syntax: .public (here [targets (: (<code>.Parser (List Target)) - (|> ..target - <>.some - (<>.else (list))))]) +(syntax: .public (here [targets (is (<code>.Parser (List Target)) + (|> ..target + <>.some + (<>.else (list))))]) (do [! meta.monad] [location meta.location locals meta.locals @@ -571,20 +571,20 @@ ... later bindings overshadow earlier ones if they have the same name. list.reversed (dictionary.of_list text.hash))] - targets (: (Meta (List Target)) - (case targets - {.#End} - (|> environment - dictionary.keys - (list#each (function (_ local) [local {.#None}])) - in) - - _ - (monad.each ! (function (_ [name format]) - (if (dictionary.key? environment name) - (in [name format]) - (function.constant (exception.except ..unknown_local_binding [name])))) - targets)))] + targets (is (Meta (List Target)) + (case targets + {.#End} + (|> environment + dictionary.keys + (list#each (function (_ local) [local {.#None}])) + in) + + _ + (monad.each ! (function (_ [name format]) + (if (dictionary.key? environment name) + (in [name format]) + (function.constant (exception.except ..unknown_local_binding [name])))) + targets)))] (in (list (` (..log! ("lux text concat" (~ (code.text (%.format (%.location location) text.new_line))) ((~! exception.report) diff --git a/stdlib/source/library/lux/documentation.lux b/stdlib/source/library/lux/documentation.lux index f6640a9b2..3d4cdcced 100644 --- a/stdlib/source/library/lux/documentation.lux +++ b/stdlib/source/library/lux/documentation.lux @@ -519,11 +519,11 @@ ... Type (let [(~ g!type) ("lux in-module" (~ g!module) - (.:of (~ (code.symbol name))))] + (.type_of (~ (code.symbol name))))] ((~! md.code) "clojure" (~ (if (type#= .Type def_type) (` (|> (~ (code.symbol name)) - (:as .Type) + (as .Type) ((~! type.anonymous)) ((~! ..type_definition) (~ g!module) @@ -582,11 +582,11 @@ (syntax: .public (default [[name parameters] ..declaration]) (let [[_ short] name] - (in (list (` (: (.List ..Definition) - (list [..#definition (~ (code.text short)) - ..#documentation ((~! ..minimal_definition_documentation) - ((~ (code.symbol name)) - (~+ (list#each code.local_symbol parameters))))]))))))) + (in (list (` (is (.List ..Definition) + (list [..#definition (~ (code.text short)) + ..#documentation ((~! ..minimal_definition_documentation) + ((~ (code.symbol name)) + (~+ (list#each code.local_symbol parameters))))]))))))) (syntax: .public (documentation: [[name parameters] ..declaration extra (<>.some <code>.any)]) @@ -630,18 +630,18 @@ subs (<code>.tuple (<>.some <code>.any))]) (do meta.monad [expected (meta.exports name)] - (in (list (` (: (List Module) - (list& [..#module (~ (code.text name)) - ..#description (~ description) - ..#expected ((~! ..expected) - (~ (code.text (|> expected - (list#each product.left) - ..expected_format)))) - ..#definitions ((~! list.together) (list (~+ definitions)))] - ($_ (# (~! list.monoid) (~' composite)) - (: (List Module) - (# (~! list.monoid) (~' identity))) - (~+ subs))))))))) + (in (list (` (is (List Module) + (list& [..#module (~ (code.text name)) + ..#description (~ description) + ..#expected ((~! ..expected) + (~ (code.text (|> expected + (list#each product.left) + ..expected_format)))) + ..#definitions ((~! list.together) (list (~+ definitions)))] + ($_ (# (~! list.monoid) (~' composite)) + (is (List Module) + (# (~! list.monoid) (~' identity))) + (~+ subs))))))))) (def: listing (-> (List Text) (Markdown Block)) @@ -706,5 +706,5 @@ (text#< (the #module right) (the #module left)))) (list#each ..module_documentation) (list.interposed md.horizontal_rule) - (list#mix md.then (: (Markdown Block) md.empty)) + (list#mix md.then (is (Markdown Block) md.empty)) md.markdown)) diff --git a/stdlib/source/library/lux/ffi.jvm.lux b/stdlib/source/library/lux/ffi.jvm.lux index f9d3dd004..446f2e738 100644 --- a/stdlib/source/library/lux/ffi.jvm.lux +++ b/stdlib/source/library/lux/ffi.jvm.lux @@ -1,6 +1,6 @@ (.using [library - [lux {"-" Primitive Type type int char :as} + [lux {"-" Primitive Type type int char as} ["[0]" meta] [abstract ["[0]" monad {"+" do}]] @@ -115,9 +115,9 @@ (-> (Type Value) Text Code Code) (let [unboxed (..reflection unboxed)] (` (|> (~ raw) - (: (.Primitive (~ (code.text <pre>)))) + (is (.Primitive (~ (code.text <pre>)))) "jvm object cast" - (: (.Primitive (~ (code.text <post>))))))))] + (is (.Primitive (~ (code.text <post>))))))))] [unbox boxed unboxed] [box unboxed boxed] @@ -126,11 +126,11 @@ (template [<name> <op> <from> <to>] [(template: .public (<name> value) [(|> value - (: <from>) + (is <from>) "jvm object cast" <op> "jvm object cast" - (: <to>))])] + (is <to>))])] [byte_to_long "jvm conversion byte-to-long" ..Byte ..Long] @@ -424,8 +424,8 @@ (-> Text Text Text (Parser Code)) (do <>.monad [.let [dotted_name (format "::" field_name)] - [_ _ value] (: (Parser [Any Any Code]) - (<code>.form ($_ <>.and (<code>.this! (' :=)) (<code>.this! (code.symbol ["" dotted_name])) <code>.any)))] + [_ _ value] (is (Parser [Any Any Code]) + (<code>.form ($_ <>.and (<code>.this! (' :=)) (<code>.this! (code.symbol ["" dotted_name])) <code>.any)))] (in (`' ("jvm member put virtual" (~ (code.text class_name)) (~ (code.text field_name)) @@ -472,9 +472,9 @@ (def: (constructor_parser class_name arguments) (-> Text (List Argument) (Parser Code)) (do <>.monad - [args (: (Parser (List Code)) - (<code>.form (<>.after (<code>.this! (' ::new!)) - (<code>.tuple (<>.exactly (list.size arguments) <code>.any)))))] + [args (is (Parser (List Code)) + (<code>.form (<>.after (<code>.this! (' ::new!)) + (<code>.tuple (<>.exactly (list.size arguments) <code>.any)))))] (in (` ("jvm member invoke constructor" (~ (code.text class_name)) (~+ (|> args (list.zipped/2 (list#each product.right arguments)) @@ -484,9 +484,9 @@ (-> Text Text (List Argument) (Parser Code)) (do <>.monad [.let [dotted_name (format "::" method_name "!")] - args (: (Parser (List Code)) - (<code>.form (<>.after (<code>.this! (code.symbol ["" dotted_name])) - (<code>.tuple (<>.exactly (list.size arguments) <code>.any)))))] + args (is (Parser (List Code)) + (<code>.form (<>.after (<code>.this! (code.symbol ["" dotted_name])) + (<code>.tuple (<>.exactly (list.size arguments) <code>.any)))))] (in (` ("jvm member invoke static" (~ (code.text class_name)) (~ (code.text method_name)) (~+ (|> args (list.zipped/2 (list#each product.right arguments)) @@ -497,9 +497,9 @@ (-> (List (Type Var)) Text (List (Type Var)) Text (List Argument) Text (Parser Code)) (do <>.monad [.let [dotted_name (format "::" method_name "!")] - args (: (Parser (List Code)) - (<code>.form (<>.after (<code>.this! (code.symbol ["" dotted_name])) - (<code>.tuple (<>.exactly (list.size arguments) <code>.any)))))] + args (is (Parser (List Code)) + (<code>.form (<>.after (<code>.this! (code.symbol ["" dotted_name])) + (<code>.tuple (<>.exactly (list.size arguments) <code>.any)))))] (in (` (<jvm_op> [(~+ (list#each (|>> ..signature code.text) class_vars))] (~ (code.text class_name)) (~ (code.text method_name)) [(~+ (list#each (|>> ..signature code.text) type_vars))] @@ -582,10 +582,10 @@ (-> (List (Type Var)) (Parser (Type Class)))) (do <>.monad [.let [class_name^ (..valid_class_name type_vars)] - [name parameters] (: (Parser [External (List (Type Parameter))]) - ($_ <>.either - (<>.and class_name^ (<>#in (list))) - (<code>.form (<>.and class_name^ (<>.some (parameter^ type_vars))))))] + [name parameters] (is (Parser [External (List (Type Parameter))]) + ($_ <>.either + (<>.and class_name^ (<>#in (list))) + (<code>.form (<>.and class_name^ (<>.some (parameter^ type_vars))))))] (in (jvm.class (name.safe name) parameters)))) (exception: .public (unknown_type_variable [name Text @@ -691,12 +691,12 @@ (def: declaration^ (Parser (Type Declaration)) (do <>.monad - [[name variables] (: (Parser [External (List (Type Var))]) - (<>.either (<>.and (..valid_class_name (list)) - (<>#in (list))) - (<code>.form (<>.and (..valid_class_name (list)) - (<>.some var^))) - ))] + [[name variables] (is (Parser [External (List (Type Var))]) + (<>.either (<>.and (..valid_class_name (list)) + (<>#in (list))) + (<code>.form (<>.and (..valid_class_name (list)) + (<>.some var^))) + ))] (in (jvm.declaration name variables)))) (def: (class^ type_vars) @@ -964,9 +964,9 @@ []]}) )) (<code>.form (do <>.monad - [kind (: (Parser ImportMethodKind) - (<>.or (<code>.this! (' "static")) - (in []))) + [kind (is (Parser ImportMethodKind) + (<>.or (<code>.this! (' "static")) + (in []))) tvars (<>.else (list) ..vars^) name <code>.local_symbol ?alias import_member_alias^ @@ -1209,10 +1209,10 @@ methods (<>.some (..method_def^ class_vars))]) (do meta.monad [.let [fully_qualified_class_name full_class_name - method_parser (: (Parser Code) - (|> methods - (list#each (method->parser class_vars fully_qualified_class_name)) - (list#mix <>.either (<>.failure ""))))]] + method_parser (is (Parser Code) + (|> methods + (list#each (method->parser class_vars fully_qualified_class_name)) + (list#mix <>.either (<>.failure ""))))]] (in (list (` ("jvm class" (~ (declaration$ (jvm.declaration full_class_name class_vars))) (~ (class$ super)) @@ -1278,19 +1278,19 @@ class_type (` (.Primitive (~ (code.text class_name)))) check_type (` (.Maybe (~ class_type))) check_code (` (if ("jvm object instance?" (~ (code.text class_name)) (~ g!unchecked)) - {.#Some (.:as (~ class_type) - (~ g!unchecked))} + {.#Some (.as (~ class_type) + (~ g!unchecked))} {.#None}))] (case unchecked {.#Some unchecked} - (in (list (` (: (~ check_type) - (let [(~ g!unchecked) (~ unchecked)] - (~ check_code)))))) + (in (list (` (is (~ check_type) + (let [(~ g!unchecked) (~ unchecked)] + (~ check_code)))))) {.#None} - (in (list (` (: (-> (.Primitive "java.lang.Object") (~ check_type)) - (function ((~ g!_) (~ g!unchecked)) - (~ check_code)))))) + (in (list (` (is (-> (.Primitive "java.lang.Object") (~ check_type)) + (function ((~ g!_) (~ g!unchecked)) + (~ check_code)))))) )))) (syntax: .public (synchronized [lock <code>.any @@ -1340,18 +1340,18 @@ (let [(open "[0]") commons] (do [! meta.monad] [arg_inputs (monad.each ! - (: (-> [Bit (Type Value)] (Meta [Bit Code])) - (function (_ [maybe? _]) - (with_symbols [arg_name] - (in [maybe? arg_name])))) + (is (-> [Bit (Type Value)] (Meta [Bit Code])) + (function (_ [maybe? _]) + (with_symbols [arg_name] + (in [maybe? arg_name])))) #import_member_args) .let [input_jvm_types (list#each product.right #import_member_args) - arg_types (list#each (: (-> [Bit (Type Value)] Code) - (function (_ [maybe? arg]) - (let [arg_type (value_type (the #import_member_mode commons) arg)] - (if maybe? - (` (Maybe (~ arg_type))) - arg_type)))) + arg_types (list#each (is (-> [Bit (Type Value)] Code) + (function (_ [maybe? arg]) + (let [arg_type (value_type (the #import_member_mode commons) arg)] + (if maybe? + (` (Maybe (~ arg_type))) + arg_type)))) #import_member_args)]] (in [arg_inputs input_jvm_types arg_types]))) @@ -1372,8 +1372,8 @@ ... else (let [g!temp (` ((~' ~') (~ (code.symbol ["" " Ω "]))))] (` (let [(~ g!temp) (~ return_term)] - (if (not (..null? (.:as (.Primitive "java.lang.Object") - (~ g!temp)))) + (if (not (..null? (.as (.Primitive "java.lang.Object") + (~ g!temp)))) (~ g!temp) (panic! "Cannot produce null references from method calls.")))))) @@ -1399,28 +1399,28 @@ (template [<input?> <name> <unbox/box> <special+>] [(def: (<name> mode [unboxed raw]) (-> Primitive_Mode [(Type Value) Code] Code) - (let [[unboxed refined post] (: [(Type Value) Code (List Code)] - (case mode - {#ManualPrM} - [unboxed raw (list)] - - {#AutoPrM} - (with_expansions [<special+>' (template.spliced <special+>) - <cond_cases> (template [<primitive> <pre> <post>] - [(# jvm.equivalence = <primitive> unboxed) - (with_expansions [<post>' (template.spliced <post>)] - [<primitive> - (` (.|> (~ raw) (~+ <pre>))) - (list <post>')])] - - <special+>')] - (cond <cond_cases> - ... else - [unboxed - (if <input?> - (` ("jvm object cast" (~ raw))) - raw) - (list)])))) + (let [[unboxed refined post] (is [(Type Value) Code (List Code)] + (case mode + {#ManualPrM} + [unboxed raw (list)] + + {#AutoPrM} + (with_expansions [<special+>' (template.spliced <special+>) + <cond_cases> (template [<primitive> <pre> <post>] + [(# jvm.equivalence = <primitive> unboxed) + (with_expansions [<post>' (template.spliced <post>)] + [<primitive> + (` (.|> (~ raw) (~+ <pre>))) + (list <post>')])] + + <special+>')] + (cond <cond_cases> + ... else + [unboxed + (if <input?> + (` ("jvm object cast" (~ raw))) + raw) + (list)])))) unboxed/boxed (case (dictionary.value unboxed ..boxes) {.#Some boxed} (<unbox/box> unboxed boxed refined) @@ -1435,23 +1435,23 @@ (` (.|> (~ unboxed/boxed) (~+ post))))))] [#1 with_automatic_input_conversion ..unbox - [[jvm.boolean (list (` (.:as (.Primitive (~ (code.text box.boolean)))))) []] - [jvm.byte (list (` (.:as (.Primitive (~ (code.text box.byte)))))) []] - [jvm.short (list (` (.:as (.Primitive (~ (code.text box.short)))))) []] - [jvm.int (list (` (.: (.Primitive (~ (code.text box.int)))))) []] - [jvm.long (list (` (.:as (.Primitive (~ (code.text box.long)))))) []] - [jvm.char (list (` (.:as (.Primitive (~ (code.text box.char)))))) []] - [jvm.float (list (` (.:as (.Primitive (~ (code.text box.float)))))) []] - [jvm.double (list (` (.:as (.Primitive (~ (code.text box.double)))))) []]]] + [[jvm.boolean (list (` (.as (.Primitive (~ (code.text box.boolean)))))) []] + [jvm.byte (list (` (.as (.Primitive (~ (code.text box.byte)))))) []] + [jvm.short (list (` (.as (.Primitive (~ (code.text box.short)))))) []] + [jvm.int (list (` (.is (.Primitive (~ (code.text box.int)))))) []] + [jvm.long (list (` (.as (.Primitive (~ (code.text box.long)))))) []] + [jvm.char (list (` (.as (.Primitive (~ (code.text box.char)))))) []] + [jvm.float (list (` (.as (.Primitive (~ (code.text box.float)))))) []] + [jvm.double (list (` (.as (.Primitive (~ (code.text box.double)))))) []]]] [#0 with_automatic_output_conversion ..box - [[jvm.boolean (list) [(` (.: (.Primitive (~ (code.text box.boolean)))))]] - [jvm.byte (list) [(` (.: (.Primitive (~ (code.text box.byte)))))]] - [jvm.short (list) [(` (.: (.Primitive (~ (code.text box.short)))))]] - [jvm.int (list) [(` (.: (.Primitive (~ (code.text box.int)))))]] - [jvm.long (list) [(` (.: (.Primitive (~ (code.text box.long)))))]] - [jvm.char (list) [(` (.: (.Primitive (~ (code.text box.char)))))]] - [jvm.float (list) [(` (.: (.Primitive (~ (code.text box.float)))))]] - [jvm.double (list) [(` (.: (.Primitive (~ (code.text box.double)))))]]]] + [[jvm.boolean (list) [(` (.is (.Primitive (~ (code.text box.boolean)))))]] + [jvm.byte (list) [(` (.is (.Primitive (~ (code.text box.byte)))))]] + [jvm.short (list) [(` (.is (.Primitive (~ (code.text box.short)))))]] + [jvm.int (list) [(` (.is (.Primitive (~ (code.text box.int)))))]] + [jvm.long (list) [(` (.is (.Primitive (~ (code.text box.long)))))]] + [jvm.char (list) [(` (.is (.Primitive (~ (code.text box.char)))))]] + [jvm.float (list) [(` (.is (.Primitive (~ (code.text box.float)))))]] + [jvm.double (list) [(` (.is (.Primitive (~ (code.text box.double)))))]]]] ) (def: (un_quoted quoted) @@ -1464,8 +1464,8 @@ (list.zipped/2 classes) (list#each (function (_ [class [maybe? input]]) (|> (if maybe? - (` (: (.Primitive (~ (code.text (..reflection class)))) - ((~! !!!) (~ (..un_quoted input))))) + (` (is (.Primitive (~ (code.text (..reflection class)))) + ((~! !!!) (~ (..un_quoted input))))) (..un_quoted input)) [class] (with_automatic_input_conversion mode)))))) @@ -1489,21 +1489,21 @@ {#EnumDecl enum_members} (with_symbols [g!_] (do meta.monad - [.let [enum_type (: Code - (case class_tvars - {.#End} - (` (.Primitive (~ (code.text full_name)))) - - _ - (let [=class_tvars (list#each ..var$' class_tvars)] - (` (All ((~ g!_) (~+ =class_tvars)) - (.Primitive (~ (code.text full_name)) [(~+ =class_tvars)])))))) - getter_interop (: (-> Text Code) - (function (_ name) - (let [getter_name (code.symbol ["" (..import_name import_format method_prefix name)])] - (` (def: (~ getter_name) - (~ enum_type) - (~ (get_static_field full_name name)))))))]] + [.let [enum_type (is Code + (case class_tvars + {.#End} + (` (.Primitive (~ (code.text full_name)))) + + _ + (let [=class_tvars (list#each ..var$' class_tvars)] + (` (All ((~ g!_) (~+ =class_tvars)) + (.Primitive (~ (code.text full_name)) [(~+ =class_tvars)])))))) + getter_interop (is (-> Text Code) + (function (_ name) + (let [getter_name (code.symbol ["" (..import_name import_format method_prefix name)])] + (` (def: (~ getter_name) + (~ enum_type) + (~ (get_static_field full_name name)))))))]] (in (list#each getter_interop enum_members)))) {#ConstructorDecl [commons _]} @@ -1531,51 +1531,51 @@ [.let [def_name (code.symbol ["" (..import_name import_format method_prefix (the #import_member_alias commons))]) (open "[0]") commons (open "[0]") method - [jvm_op object_ast] (: [Text (List Code)] - (case #import_member_kind - {#StaticIMK} - ["jvm member invoke static" - (list)] - - {#VirtualIMK} - (case kind - {#Class} - ["jvm member invoke virtual" - (list g!obj)] - - {#Interface} - ["jvm member invoke interface" - (list g!obj)] - ))) + [jvm_op object_ast] (is [Text (List Code)] + (case #import_member_kind + {#StaticIMK} + ["jvm member invoke static" + (list)] + + {#VirtualIMK} + (case kind + {#Class} + ["jvm member invoke virtual" + (list g!obj)] + + {#Interface} + ["jvm member invoke interface" + (list g!obj)] + ))) method_return (the #import_method_return method) - callC (: Code - (` ((~ (code.text jvm_op)) - [(~+ (list#each ..var$ class_tvars))] - (~ (code.text full_name)) - (~ (code.text #import_method_name)) - [(~+ (list#each ..var$ (the #import_member_tvars commons)))] - (~+ (|> object_ast - (list#each ..un_quoted) - (list.zipped/2 (list (jvm.class full_name (list)))) - (list#each (with_automatic_input_conversion (the #import_member_mode commons))))) - (~+ (|> (jvm_invoke_inputs (the #import_member_mode commons) input_jvm_types arg_function_inputs) - (list.zipped/2 input_jvm_types) - (list#each ..decorate_input)))))) - jvm_interop (: Code - (case (jvm.void? method_return) - {.#Left method_return} - (|> [method_return - callC] - (with_automatic_output_conversion (the #import_member_mode commons)) - (with_return_maybe member false method_return) - (with_return_try member) - (with_return_io member)) - - - {.#Right method_return} - (|> callC - (with_return_try member) - (with_return_io member))))]] + callC (is Code + (` ((~ (code.text jvm_op)) + [(~+ (list#each ..var$ class_tvars))] + (~ (code.text full_name)) + (~ (code.text #import_method_name)) + [(~+ (list#each ..var$ (the #import_member_tvars commons)))] + (~+ (|> object_ast + (list#each ..un_quoted) + (list.zipped/2 (list (jvm.class full_name (list)))) + (list#each (with_automatic_input_conversion (the #import_member_mode commons))))) + (~+ (|> (jvm_invoke_inputs (the #import_member_mode commons) input_jvm_types arg_function_inputs) + (list.zipped/2 input_jvm_types) + (list#each ..decorate_input)))))) + jvm_interop (is Code + (case (jvm.void? method_return) + {.#Left method_return} + (|> [method_return + callC] + (with_automatic_output_conversion (the #import_member_mode commons)) + (with_return_maybe member false method_return) + (with_return_try member) + (with_return_io member)) + + + {.#Right method_return} + (|> callC + (with_return_try member) + (with_return_io member))))]] (in (list (` ((~! syntax:) ((~ def_name) [(~+ (syntax_inputs (list#each product.right arg_function_inputs))) (~+ (syntax_inputs object_ast))]) ((~' in) (.list (.` (~ jvm_interop)))))))))) @@ -1602,27 +1602,27 @@ getter_body)] (in (` ((~! syntax:) (~ getter_call) ((~' in) (.list (.` (~ getter_body))))))))) - setter_interop (: (Meta (List Code)) - (if _#import_field_setter? - (with_symbols [g!obj g!value] - (let [setter_call (if _#import_field_static? - (` ((~ setter_name) [(~ g!value) (~! <code>.any)])) - (` ((~ setter_name) [(~ g!value) (~! <code>.any) - (~ g!obj) (~! <code>.any)]))) - setter_value (|> [_#import_field_type (..un_quoted g!value)] - (with_automatic_input_conversion _#import_field_mode)) - setter_value (if _#import_field_maybe? - (` ((~! !!!) (~ setter_value))) - setter_value) - setter_command (format (if _#import_field_static? "jvm putstatic" "jvm putfield") - ":" full_name ":" _#import_field_name) - g!obj+ (: (List Code) - (if _#import_field_static? - (list) - (list (..un_quoted g!obj))))] - (in (list (` ((~! syntax:) (~ setter_call) - ((~' in) (.list (.` ((~! io.io) ((~ (code.text setter_command)) (~+ g!obj+) (~ setter_value)))))))))))) - (in (list))))] + setter_interop (is (Meta (List Code)) + (if _#import_field_setter? + (with_symbols [g!obj g!value] + (let [setter_call (if _#import_field_static? + (` ((~ setter_name) [(~ g!value) (~! <code>.any)])) + (` ((~ setter_name) [(~ g!value) (~! <code>.any) + (~ g!obj) (~! <code>.any)]))) + setter_value (|> [_#import_field_type (..un_quoted g!value)] + (with_automatic_input_conversion _#import_field_mode)) + setter_value (if _#import_field_maybe? + (` ((~! !!!) (~ setter_value))) + setter_value) + setter_command (format (if _#import_field_static? "jvm putstatic" "jvm putfield") + ":" full_name ":" _#import_field_name) + g!obj+ (is (List Code) + (if _#import_field_static? + (list) + (list (..un_quoted g!obj))))] + (in (list (` ((~! syntax:) (~ setter_call) + ((~' in) (.list (.` ((~! io.io) ((~ (code.text setter_command)) (~+ g!obj+) (~ setter_value)))))))))))) + (in (list))))] (in (list& getter_interop setter_interop))) ))) @@ -1638,12 +1638,12 @@ (All (_ a) (-> (.Primitive "java.lang.Class" [a]) Bit)) (|>> ("jvm member invoke virtual" [] "java.lang.Class" "isInterface" []) "jvm object cast" - (: ..Boolean) - (.:as Bit))) + (is ..Boolean) + (.as Bit))) (def: load_class (-> External (Try (.Primitive "java.lang.Class" [Any]))) - (|>> (.:as (.Primitive "java.lang.String")) + (|>> (.as (.Primitive "java.lang.String")) ["Ljava/lang/String;"] ("jvm member invoke static" [] "java.lang.Class" "forName" []) try)) @@ -1674,8 +1674,8 @@ (syntax: .public (array [type (..type^ (list)) size <code>.any]) (let [g!size (` (|> (~ size) - (.: .Nat) - (.:as (.Primitive (~ (code.text box.long)))) + (.is .Nat) + (.as (.Primitive (~ (code.text box.long)))) "jvm object cast" "jvm conversion long-to-int"))] (`` (cond (~~ (template [<primitive> <array_op>] @@ -1691,8 +1691,8 @@ [jvm.double "jvm array new double"] [jvm.char "jvm array new char"])) ... else - (in (list (` (: (~ (value_type {#ManualPrM} (jvm.array type))) - ("jvm array new object" (~ g!size)))))))))) + (in (list (` (is (~ (value_type {#ManualPrM} (jvm.array type))) + ("jvm array new object" (~ g!size)))))))))) (exception: .public (cannot_convert_to_jvm_type [type .Type]) (exception.report @@ -1762,18 +1762,18 @@ ... else (# meta.monad each (jvm.class name) - (: (Meta (List (Type Parameter))) - (monad.each meta.monad - (function (_ paramLT) - (do meta.monad - [paramJT (lux_type->jvm_type context paramLT)] - (case (parser.parameter? paramJT) - {.#Some paramJT} - (in paramJT) - - {.#None} - <failure>))) - params))))) + (is (Meta (List (Type Parameter))) + (monad.each meta.monad + (function (_ paramLT) + (do meta.monad + [paramJT (lux_type->jvm_type context paramLT)] + (case (parser.parameter? paramJT) + {.#Some paramJT} + (in paramJT) + + {.#None} + <failure>))) + params))))) {.#Apply A F} (case (type.applied (list A) F) @@ -1824,8 +1824,8 @@ (in (list (` (.|> ((~ g!extension) (~ array)) "jvm conversion int-to-long" "jvm object cast" - (.: (.Primitive (~ (code.text box.long)))) - (.:as .Nat)))))) + (.is (.Primitive (~ (code.text box.long)))) + (.as .Nat)))))) _ (with_symbols [g!array] @@ -1841,8 +1841,8 @@ context meta.type_context array_jvm_type (lux_type->jvm_type context array_type) .let [g!idx (` (.|> (~ idx) - (.: .Nat) - (.:as (.Primitive (~ (code.text box.long)))) + (.is .Nat) + (.as (.Primitive (~ (code.text box.long)))) "jvm object cast" "jvm conversion long-to-int"))]] (`` (cond (~~ (template [<primitive> <extension> <box>] @@ -1851,7 +1851,7 @@ array_jvm_type) (in (list (` (.|> (<extension> (~ g!idx) (~ array)) "jvm object cast" - (.: (.Primitive (~ (code.text <box>))))))))] + (.is (.Primitive (~ (code.text <box>))))))))] [jvm.boolean "jvm array read boolean" box.boolean] [jvm.byte "jvm array read byte" box.byte] @@ -1880,8 +1880,8 @@ context meta.type_context array_jvm_type (lux_type->jvm_type context array_type) .let [g!idx (` (.|> (~ idx) - (.: .Nat) - (.:as (.Primitive (~ (code.text box.long)))) + (.is .Nat) + (.as (.Primitive (~ (code.text box.long)))) "jvm object cast" "jvm conversion long-to-int"))]] (`` (cond (~~ (template [<primitive> <extension> <box>] @@ -1889,7 +1889,7 @@ (jvm.array <primitive>) array_jvm_type) (let [g!value (` (.|> (~ value) - (.:as (.Primitive (~ (code.text <box>)))) + (.as (.Primitive (~ (code.text <box>)))) "jvm object cast"))] (in (list (` (<extension> (~ g!idx) (~ g!value) (~ array))))))] @@ -1921,23 +1921,23 @@ "Signature" (..signature type) "Reflection" (..reflection type))) -(syntax: .public (:as [type (..type^ (list)) - object <code>.any]) +(syntax: .public (as [type (..type^ (list)) + object <code>.any]) (case [(parser.array? type) (parser.class? type)] (^.or [{.#Some _} _] [_ {.#Some _}]) - (in (list (` (.: (~ (..value_type {#ManualPrM} type)) - ("jvm object cast" (~ object)))))) + (in (list (` (.is (~ (..value_type {#ManualPrM} type)) + ("jvm object cast" (~ object)))))) _ (meta.failure (exception.error ..cannot_cast_to_non_object [type])))) (template [<forward> <from> <to> <backward>] [(template: .public (<forward> it) - [(|> it (: <from>) (:as <to>))]) + [(|> it (is <from>) (as <to>))]) (template: .public (<backward> it) - [(|> it (: <to>) (:as <from>))])] + [(|> it (is <to>) (as <from>))])] [as_boolean .Bit ..Boolean of_boolean] [as_long .Int ..Long of_long] @@ -1947,10 +1947,10 @@ (template [<forward> <from> <$> <mid> <$'> <to> <backward>] [(template: .public (<forward> it) - [(|> it (: <from>) (:as <mid>) <$> (: <to>))]) + [(|> it (is <from>) (as <mid>) <$> (is <to>))]) (template: .public (<backward> it) - [(|> it (: <to>) <$'> (: <mid>) (:as <from>))])] + [(|> it (is <to>) <$'> (is <mid>) (as <from>))])] [as_byte .Int ..long_to_byte ..Long ..byte_to_long ..Byte of_byte] [as_short .Int ..long_to_short ..Long ..short_to_long ..Short of_short] diff --git a/stdlib/source/library/lux/ffi.lux b/stdlib/source/library/lux/ffi.lux index f5b578b62..6554a4082 100644 --- a/stdlib/source/library/lux/ffi.lux +++ b/stdlib/source/library/lux/ffi.lux @@ -264,7 +264,7 @@ <lux_?> <host_?>] [(def: .public (<lux_it> _) (-> Any Nothing) - (:expected (<host_it>))) + (as_expected (<host_it>))) (def: .public <lux_?> (-> Any Bit) @@ -385,10 +385,10 @@ (..input_type input))))) (.exec (~+ import!) - (.:expected + (.as_expected (~ (<| (..input_term input) (..lux_optional :output:) - (` (<apply> (.:expected (~ source)) + (` (<apply> (.as_expected (~ source)) [(~+ (list#each ..host_optional g!parameters))])))))))))) (def: (namespaced namespace class alias member) @@ -409,8 +409,8 @@ {.#Item head tail} (list#mix (.function (_ sub super) (` (<get> (~ (code.text sub)) - (.:as (..Object .Any) - (~ super))))) + (.as (..Object .Any) + (~ super))))) (` (<import> (~ (code.text head)))) tail) @@ -427,7 +427,7 @@ (~ (..output_type :output:)) (.exec (~+ import!) - (.:expected + (.as_expected (~ (<| (lux_optional :output:) (` (<constant> (~ (code.text (..host_path (the #name it)))))))))))))) @@ -455,12 +455,12 @@ (~ (|> :output: ..output_type (..input_type input))))) - (.:expected + (.as_expected (~ (<| (..input_term input) (..lux_optional :output:) (` (<new> (~ (for @.js (` (<constant> (~ (code.text (..host_path class_name))))) - @.python (` (.:as ..Function - (~ (..imported 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) @@ -475,12 +475,12 @@ (.# (~! meta.monad) (~' in) (.list (`' (.exec (~+ import!) - (.:as (~ (..output_type :field:)) - (~ (<| (lux_optional :field:) - (for @.js (` (<constant> (~ (code.text (%.format (..host_path class_name) "." field))))) - @.ruby (` (<constant> (~ (code.text (%.format (..host_path class_name) "::" field))))) - (` (<get> (~ (code.text field)) - (~ (..imported class_name)))))))))))))))) + (.as (~ (..output_type :field:)) + (~ (<| (lux_optional :field:) + (for @.js (` (<constant> (~ (code.text (%.format (..host_path class_name) "." field))))) + @.ruby (` (<constant> (~ (code.text (%.format (..host_path class_name) "::" field))))) + (` (<get> (~ (code.text field)) + (~ (..imported class_name)))))))))))))))) (def: (virtual_field_definition [class_name class_parameters] alias namespace it) (-> Declaration Alias Namespace (Named Output) Code) @@ -497,7 +497,7 @@ (.All ((~ g!it) (~+ g!variables)) (.-> (~ g!class) (~ (..output_type :field:)))) - (.:expected + (.as_expected (~ (<| (lux_optional :field:) (` (<get> (~ (code.text name)) (~ g!it)))))))))) @@ -519,8 +519,8 @@ (for @.js (` (<constant> (~ (code.text (%.format (..host_path class_name) "." method))))) @.ruby (` (<constant> (~ (code.text (%.format (..host_path class_name) "::" method))))) (` (<get> (~ (code.text method)) - (.:as (..Object .Any) - (~ (..imported class_name)))))))))) + (.as (..Object .Any) + (~ (..imported class_name)))))))))) (def: (virtual_method_definition [class_name class_parameters] alias namespace it) (-> Declaration Alias Namespace (Named Procedure) Code) @@ -544,7 +544,7 @@ (~ (|> :output: ..output_type (..input_type input))))) - (.:expected + (.as_expected (~ (<| (..input_term input) (..lux_optional :output:) (` (<do> (~ (code.text method)) @@ -559,13 +559,13 @@ (syntax: .public (import: [host_module (<>.maybe <code>.text) it ..import]) - (let [host_module_import! (: (List Code) - (case host_module - {.#Some host_module} - (list (` (<import> (~ (code.text host_module))))) + (let [host_module_import! (is (List Code) + (case host_module + {.#Some host_module} + (list (` (<import> (~ (code.text host_module))))) - {.#None} - (list)))] + {.#None} + (list)))] (case it {#Global it} (in (list (..global_definition host_module_import! it))) @@ -608,12 +608,12 @@ (<code>.tuple (<>.some (<>.and <code>.any <code>.any))))) type <code>.any term <code>.any]) - (in (list (` (.<| (.:as ..Function) + (in (list (` (.<| (.as ..Function) (<function> (~ (code.nat (list.size inputs)))) - (.:as (.-> [(~+ (list.repeated (list.size inputs) (` .Any)))] - .Any)) - (.: (.-> [(~+ (list#each product.right inputs))] - (~ type))) + (.as (.-> [(~+ (list.repeated (list.size inputs) (` .Any)))] + .Any)) + (.is (.-> [(~+ (list#each product.right inputs))] + (~ type))) (.function ((~ (code.local_symbol self)) [(~+ (list#each product.left inputs))]) (~ term)))))))) @@ -626,24 +626,24 @@ (let [global (` ("js constant" (~ (code.text head))))] (case tail {.#End} - (in (list (` (: (.Maybe (~ type)) - (case (..type_of (~ global)) - "undefined" - {.#None} + (in (list (` (is (.Maybe (~ type)) + (case (..type_of (~ global)) + "undefined" + {.#None} - (~ g!_) - {.#Some (:as (~ type) (~ global))}))))) + (~ g!_) + {.#Some (as (~ type) (~ global))}))))) {.#Item [next tail]} (let [separator "."] - (in (list (` (: (.Maybe (~ type)) - (case (..type_of (~ global)) - "undefined" - {.#None} + (in (list (` (is (.Maybe (~ type)) + (case (..type_of (~ global)) + "undefined" + {.#None} - (~ g!_) - (..global (~ type) [(~ (code.local_symbol (%.format head "." next))) - (~+ (list#each code.local_symbol tail))]))))))))))) + (~ g!_) + (..global (~ type) [(~ (code.local_symbol (%.format head "." next))) + (~+ (list#each code.local_symbol tail))]))))))))))) (template: (!defined? <global>) [(.case (..global Any <global>) @@ -667,7 +667,7 @@ (|> (..global (Object Any) [process]) (maybe#each (|>> [] ("js apply" ("js constant" "Object.prototype.toString.call")) - (:as Text) + (as Text) (text#= "[object process]"))) (maybe.else false))) ) diff --git a/stdlib/source/library/lux/ffi.old.lux b/stdlib/source/library/lux/ffi.old.lux index 2cd19ade0..697177697 100644 --- a/stdlib/source/library/lux/ffi.old.lux +++ b/stdlib/source/library/lux/ffi.old.lux @@ -1,6 +1,6 @@ (.using [library - [lux {"-" :as type} + [lux {"-" as type} ["[0]" type ("[1]#[0]" equivalence)] [abstract ["[0]" monad {"+" Monad do}] @@ -65,10 +65,10 @@ (template [<forward> <from> <to> <backward>] [(template: .public (<forward> it) - [(|> it (: <from>) (.:as (Primitive <to>)))]) + [(|> it (is <from>) (.as (Primitive <to>)))]) (template: .public (<backward> it) - [(|> it (: (Primitive <to>)) (.:as <from>))])] + [(|> it (is (Primitive <to>)) (.as <from>))])] [as_boolean .Bit "java.lang.Boolean" of_boolean] [as_long .Int "java.lang.Long" of_long] @@ -78,10 +78,10 @@ (template [<forward> <from> <$> <mid> <$'> <to> <backward>] [(template: .public (<forward> it) - [(|> it (: <from>) (.:as (Primitive <mid>)) <$> (: (Primitive <to>)))]) + [(|> it (is <from>) (.as (Primitive <mid>)) <$> (is (Primitive <to>)))]) (template: .public (<backward> it) - [(|> it (: (Primitive <to>)) <$'> (: (Primitive <mid>)) (.:as <from>))])] + [(|> it (is (Primitive <to>)) <$'> (is (Primitive <mid>)) (.as <from>))])] [as_byte .Int ..long_to_byte "java.lang.Long" ..byte_to_long "java.lang.Byte" of_byte] [as_short .Int ..long_to_short "java.lang.Long" ..short_to_long "java.lang.Short" of_short] @@ -380,14 +380,14 @@ (def: (class_decl_type$ (open "[0]")) (-> Class_Declaration Code) - (let [=params (list#each (: (-> Type_Parameter Code) - (function (_ [pname pbounds]) - (case pbounds - {.#End} - (code.symbol ["" pname]) - - {.#Item bound1 _} - (class_type {#ManualPrM} #class_params bound1)))) + (let [=params (list#each (is (-> Type_Parameter Code) + (function (_ [pname pbounds]) + (case pbounds + {.#End} + (code.symbol ["" pname]) + + {.#Item bound1 _} + (class_type {#ManualPrM} #class_params bound1)))) #class_params)] (` (Primitive (~ (code.text (safe #class_name))) [(~+ =params)])))) @@ -457,8 +457,8 @@ (-> Text Text (Parser Code)) (do <>.monad [.let [dotted_name (format "::" field_name)] - [_ _ value] (: (Parser [Any Any Code]) - (<code>.form ($_ <>.and (<code>.this! (' :=)) (<code>.this! (code.symbol ["" dotted_name])) <code>.any)))] + [_ _ value] (is (Parser [Any Any Code]) + (<code>.form ($_ <>.and (<code>.this! (' :=)) (<code>.this! (code.symbol ["" dotted_name])) <code>.any)))] (in (`' ((~ (code.text (format "jvm putfield" ":" class_name ":" field_name))) _jvm_this (~ value)))))) (def: (pre_walk_replace f input) @@ -497,10 +497,10 @@ (def: (constructor_parser params class_name arg_decls) (-> (List Type_Parameter) Text (List ArgDecl) (Parser Code)) (do <>.monad - [args (: (Parser (List Code)) - (<code>.form (<>.after (<code>.this! (' ::new!)) - (<code>.tuple (<>.exactly (list.size arg_decls) <code>.any))))) - .let [arg_decls' (: (List Text) (list#each (|>> product.right (simple_class$ params)) arg_decls))]] + [args (is (Parser (List Code)) + (<code>.form (<>.after (<code>.this! (' ::new!)) + (<code>.tuple (<>.exactly (list.size arg_decls) <code>.any))))) + .let [arg_decls' (is (List Text) (list#each (|>> product.right (simple_class$ params)) arg_decls))]] (in (` ((~ (code.text (format "jvm new" ":" class_name ":" (text.interposed "," arg_decls')))) (~+ args)))))) @@ -508,10 +508,10 @@ (-> (List Type_Parameter) Text Text (List ArgDecl) (Parser Code)) (do <>.monad [.let [dotted_name (format "::" method_name "!")] - args (: (Parser (List Code)) - (<code>.form (<>.after (<code>.this! (code.symbol ["" dotted_name])) - (<code>.tuple (<>.exactly (list.size arg_decls) <code>.any))))) - .let [arg_decls' (: (List Text) (list#each (|>> product.right (simple_class$ params)) arg_decls))]] + args (is (Parser (List Code)) + (<code>.form (<>.after (<code>.this! (code.symbol ["" dotted_name])) + (<code>.tuple (<>.exactly (list.size arg_decls) <code>.any))))) + .let [arg_decls' (is (List Text) (list#each (|>> product.right (simple_class$ params)) arg_decls))]] (in (`' ((~ (code.text (format "jvm invokestatic" ":" class_name ":" method_name ":" (text.interposed "," arg_decls')))) (~+ args)))))) @@ -520,10 +520,10 @@ (-> (List Type_Parameter) Text Text (List ArgDecl) (Parser Code)) (do <>.monad [.let [dotted_name (format "::" method_name "!")] - args (: (Parser (List Code)) - (<code>.form (<>.after (<code>.this! (code.symbol ["" dotted_name])) - (<code>.tuple (<>.exactly (list.size arg_decls) <code>.any))))) - .let [arg_decls' (: (List Text) (list#each (|>> product.right (simple_class$ params)) arg_decls))]] + args (is (Parser (List Code)) + (<code>.form (<>.after (<code>.this! (code.symbol ["" dotted_name])) + (<code>.tuple (<>.exactly (list.size arg_decls) <code>.any))))) + .let [arg_decls' (is (List Text) (list#each (|>> product.right (simple_class$ params)) arg_decls))]] (in (`' ((~ (code.text (format <jvm_op> ":" class_name ":" method_name ":" (text.interposed "," arg_decls')))) (~' _jvm_this) (~+ args))))))] @@ -933,9 +933,9 @@ #import_member_io? io?] []]}))) (<code>.form (do <>.monad - [kind (: (Parser ImportMethodKind) - (<>.or (<code>.this! (' "static")) - (in []))) + [kind (is (Parser ImportMethodKind) + (<>.or (<code>.this! (' "static")) + (in []))) tvars ..type_params^ name <code>.local_symbol ?alias import_member_alias^ @@ -1128,8 +1128,8 @@ (let [super_replacer (parser_replacer (<code>.form (do <>.monad [_ (<code>.this! (' ::super!)) args (<code>.tuple (<>.exactly (list.size arg_decls) <code>.any)) - .let [arg_decls' (: (List Text) (list#each (|>> product.right (simple_class$ (list))) - arg_decls))]] + .let [arg_decls' (is (List Text) (list#each (|>> product.right (simple_class$ (list))) + arg_decls))]] (in (`' ((~ (code.text (format "jvm invokespecial" ":" (the #super_class_name super_class) ":" name @@ -1284,19 +1284,19 @@ class_type (` (.Primitive (~ (code.text class_name)))) check_type (` (.Maybe (~ class_type))) check_code (` (if ((~ (code.text (format "jvm instanceof" ":" class_name))) (~ g!unchecked)) - {.#Some (.:as (~ class_type) - (~ g!unchecked))} + {.#Some (.as (~ class_type) + (~ g!unchecked))} {.#None}))] (case unchecked {.#Some unchecked} - (in (list (` (: (~ check_type) - (let [(~ g!unchecked) (~ unchecked)] - (~ check_code)))))) + (in (list (` (is (~ check_type) + (let [(~ g!unchecked) (~ unchecked)] + (~ check_code)))))) {.#None} - (in (list (` (: (-> (Primitive "java.lang.Object") (~ check_type)) - (function ((~ g!_) (~ g!unchecked)) - (~ check_code)))))) + (in (list (` (is (-> (Primitive "java.lang.Object") (~ check_type)) + (function ((~ g!_) (~ g!unchecked)) + (~ check_code)))))) )))) (syntax: .public (synchronized [lock <code>.any @@ -1344,20 +1344,20 @@ (let [(open "[0]") commons] (do [! meta.monad] [arg_inputs (monad.each ! - (: (-> [Bit GenericType] (Meta [Bit Code])) - (function (_ [maybe? _]) - (with_symbols [arg_name] - (in [maybe? arg_name])))) + (is (-> [Bit GenericType] (Meta [Bit Code])) + (function (_ [maybe? _]) + (with_symbols [arg_name] + (in [maybe? arg_name])))) #import_member_args) - .let [arg_classes (: (List Text) - (list#each (|>> product.right (simple_class$ (list#composite type_params #import_member_tvars))) - #import_member_args)) - arg_types (list#each (: (-> [Bit GenericType] Code) - (function (_ [maybe? arg]) - (let [arg_type (class_type (the #import_member_mode commons) type_params arg)] - (if maybe? - (` (Maybe (~ arg_type))) - arg_type)))) + .let [arg_classes (is (List Text) + (list#each (|>> product.right (simple_class$ (list#composite type_params #import_member_tvars))) + #import_member_args)) + arg_types (list#each (is (-> [Bit GenericType] Code) + (function (_ [maybe? arg]) + (let [arg_type (class_type (the #import_member_mode commons) type_params arg)] + (if maybe? + (` (Maybe (~ arg_type))) + arg_type)))) #import_member_args)]] (in [arg_inputs arg_classes arg_types]))) @@ -1372,8 +1372,8 @@ (` (??? (~ return_term))) (let [g!temp (` ((~' ~') (~ (code.symbol ["" " Ω "]))))] (` (let [(~ g!temp) (~ return_term)] - (if (not (..null? (.:as (Primitive "java.lang.Object") - (~ g!temp)))) + (if (not (..null? (.as (Primitive "java.lang.Object") + (~ g!temp)))) (~ g!temp) (panic! (~ (code.text (format "Cannot produce null references from method calls @ " (the #class_name class) @@ -1459,22 +1459,22 @@ {#EnumDecl enum_members} (macro.with_symbols [g!_] (do [! meta.monad] - [.let [enum_type (: Code - (case class_tvars - {.#End} - (` (Primitive (~ (code.text full_name)))) - - _ - (let [=class_tvars (|> class_tvars - (list.only free_type_param?) - (list#each lux_type_parameter))] - (` (All ((~ g!_) (~+ =class_tvars)) (Primitive (~ (code.text full_name)) [(~+ =class_tvars)])))))) - getter_interop (: (-> Text Code) - (function (_ name) - (let [getter_name (code.symbol ["" (..import_name import_format method_prefix name)])] - (` (def: (~ getter_name) - (~ enum_type) - ((~ (code.text (format "jvm getstatic" ":" full_name ":" name)))))))))]] + [.let [enum_type (is Code + (case class_tvars + {.#End} + (` (Primitive (~ (code.text full_name)))) + + _ + (let [=class_tvars (|> class_tvars + (list.only free_type_param?) + (list#each lux_type_parameter))] + (` (All ((~ g!_) (~+ =class_tvars)) (Primitive (~ (code.text full_name)) [(~+ =class_tvars)])))))) + getter_interop (is (-> Text Code) + (function (_ name) + (let [getter_name (code.symbol ["" (..import_name import_format method_prefix name)])] + (` (def: (~ getter_name) + (~ enum_type) + ((~ (code.text (format "jvm getstatic" ":" full_name ":" name)))))))))]] (in (list#each getter_interop enum_members)))) {#ConstructorDecl [commons _]} @@ -1495,22 +1495,22 @@ [.let [def_name (code.symbol ["" (..import_name import_format method_prefix (the #import_member_alias commons))]) (open "[0]") commons (open "[0]") method - [jvm_op object_ast] (: [Text (List Code)] - (case #import_member_kind - {#StaticIMK} - ["invokestatic" - (list)] - - {#VirtualIMK} - (case kind - {#Class} - ["invokevirtual" - (list g!obj)] - - {#Interface} - ["invokeinterface" - (list g!obj)] - ))) + [jvm_op object_ast] (is [Text (List Code)] + (case #import_member_kind + {#StaticIMK} + ["invokestatic" + (list)] + + {#VirtualIMK} + (case kind + {#Class} + ["invokevirtual" + (list g!obj)] + + {#Interface} + ["invokeinterface" + (list g!obj)] + ))) jvm_extension (code.text (format "jvm " jvm_op ":" full_name ":" #import_method_name ":" (text.interposed "," arg_classes))) jvm_interop (|> [(simple_class$ (list) (the #import_method_return method)) (` ((~ jvm_extension) (~+ (list#each un_quote object_ast)) @@ -1531,10 +1531,10 @@ typeC (if #import_field_maybe? (` (Maybe (~ base_gtype))) base_gtype) - tvar_asts (: (List Code) - (|> class_tvars - (list.only free_type_param?) - (list#each lux_type_parameter))) + tvar_asts (is (List Code) + (|> class_tvars + (list.only free_type_param?) + (list#each lux_type_parameter))) getter_name (code.symbol ["" (..import_name import_format method_prefix #import_field_name)]) setter_name (code.symbol ["" (..import_name import_format method_prefix (format #import_field_name "!"))])] getter_interop (with_symbols [g!obj] @@ -1556,27 +1556,27 @@ getter_body)] (in (` ((~! syntax:) (~ getter_call) ((~' in) (.list (.` (~ getter_body))))))))) - setter_interop (: (Meta (List Code)) - (if #import_field_setter? - (with_symbols [g!obj g!value] - (let [setter_call (if #import_field_static? - (` ((~ setter_name) [(~ g!value) (~! <code>.any)])) - (` ((~ setter_name) [(~ g!value) (~! <code>.any) - (~ g!obj) (~! <code>.any)]))) - setter_value (auto_convert_input #import_field_mode - [(simple_class$ (list) #import_field_type) (un_quote g!value)]) - setter_value (if #import_field_maybe? - (` ((~! !!!) (~ setter_value))) - setter_value) - setter_command (format (if #import_field_static? "jvm putstatic" "jvm putfield") - ":" full_name ":" #import_field_name) - g!obj+ (: (List Code) - (if #import_field_static? - (list) - (list (un_quote g!obj))))] - (in (list (` ((~! syntax:) (~ setter_call) - ((~' in) (.list (.` ((~! io.io) ((~ (code.text setter_command)) (~+ g!obj+) (~ setter_value)))))))))))) - (in (list))))] + setter_interop (is (Meta (List Code)) + (if #import_field_setter? + (with_symbols [g!obj g!value] + (let [setter_call (if #import_field_static? + (` ((~ setter_name) [(~ g!value) (~! <code>.any)])) + (` ((~ setter_name) [(~ g!value) (~! <code>.any) + (~ g!obj) (~! <code>.any)]))) + setter_value (auto_convert_input #import_field_mode + [(simple_class$ (list) #import_field_type) (un_quote g!value)]) + setter_value (if #import_field_maybe? + (` ((~! !!!) (~ setter_value))) + setter_value) + setter_command (format (if #import_field_static? "jvm putstatic" "jvm putfield") + ":" full_name ":" #import_field_name) + g!obj+ (is (List Code) + (if #import_field_static? + (list) + (list (un_quote g!obj))))] + (in (list (` ((~! syntax:) (~ setter_call) + ((~' in) (.list (.` ((~! io.io) ((~ (code.text setter_command)) (~+ g!obj+) (~ setter_value)))))))))))) + (in (list))))] (in (list& getter_interop setter_interop))) ))) @@ -1727,5 +1727,5 @@ (syntax: .public (type [type (..generic_type^ (list))]) (in (list (..class_type {#ManualPrM} (list) type)))) -(template: .public (:as type term) - [(.:as type term)]) +(template: .public (as type term) + [(.as type term)]) diff --git a/stdlib/source/library/lux/ffi.php.lux b/stdlib/source/library/lux/ffi.php.lux index cfcfec9f8..cb2c6a615 100644 --- a/stdlib/source/library/lux/ffi.php.lux +++ b/stdlib/source/library/lux/ffi.php.lux @@ -1,27 +1,27 @@ (.using - [library - [lux {"-" Alias} - ["@" target] - ["[0]" meta] - [abstract - [monad {"+" do}]] - [control - ["[0]" io] - ["[0]" maybe] - ["<>" parser ("[1]#[0]" monad) - ["<[0]>" code {"+" Parser}]]] - [data - ["[0]" product] - ["[0]" text - ["%" format]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [type - abstract] - [macro {"+" with_symbols} - [syntax {"+" syntax:}] - ["[0]" code] - ["[0]" template]]]]) + [library + [lux {"-" Alias} + ["@" target] + ["[0]" meta] + [abstract + [monad {"+" do}]] + [control + ["[0]" io] + ["[0]" maybe] + ["<>" parser ("[1]#[0]" monad) + ["<[0]>" code {"+" Parser}]]] + [data + ["[0]" product] + ["[0]" text + ["%" format]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [type + abstract] + [macro {"+" with_symbols} + [syntax {"+" syntax:}] + ["[0]" code] + ["[0]" template]]]]) (abstract: .public (Object brand) Any) @@ -228,12 +228,12 @@ (~ (|> (nullable_type outputT) (try_type try?) (io_type io?)))) - (:expected + (as_expected (~ (<| (with_io io?) (with_try try?) (without_null g!temp outputT) (` ("php apply" - (:as ..Function (~ source)) + (as ..Function (~ source)) (~+ (list#each (with_null g!temp) g!inputs))))))))))) (syntax: .public (import: [import ..import]) @@ -241,12 +241,12 @@ (case import {#Class [class alias format members]} (with_symbols [g!object] - (let [qualify (: (-> Text Code) - (function (_ member_name) - (|> format - (text.replaced "[1]" (maybe.else class alias)) - (text.replaced "[0]" member_name) - code.local_symbol))) + (let [qualify (is (-> Text Code) + (function (_ member_name) + (|> format + (text.replaced "[1]" (maybe.else class alias)) + (text.replaced "[0]" member_name) + code.local_symbol))) g!type (code.local_symbol (maybe.else class alias)) class_import (` ("php constant" (~ (code.text class))))] (in (list& (` (type: (~ g!type) @@ -257,15 +257,15 @@ (if static? (` ((~! syntax:) ((~ (qualify (maybe.else field alias))) []) (# (~! meta.monad) (~' in) - (list (` (.:as (~ (nullable_type fieldT)) - ("php constant" (~ (code.text (%.format class "::" field)))))))))) + (list (` (.as (~ (nullable_type fieldT)) + ("php constant" (~ (code.text (%.format class "::" field)))))))))) (` (def: ((~ (qualify field)) (~ g!object)) (-> (~ g!type) (~ (nullable_type fieldT))) - (:expected + (as_expected (~ (without_null g!temp fieldT (` ("php object get" (~ (code.text field)) - (:as (..Object .Any) (~ g!object)))))))))) + (as (..Object .Any) (~ g!object)))))))))) {#Method method} (case method @@ -273,8 +273,8 @@ (..make_function (qualify (maybe.else method alias)) g!temp (` ("php object get" (~ (code.text method)) - (:as (..Object .Any) - ("php constant" (~ (code.text (%.format class "::" method))))))) + (as (..Object .Any) + ("php constant" (~ (code.text (%.format class "::" method))))))) inputsT io? try? @@ -290,7 +290,7 @@ (~ (|> (nullable_type outputT) (try_type try?) (io_type io?)))) - (:expected + (as_expected (~ (<| (with_io io?) (with_try try?) (without_null g!temp outputT) @@ -314,5 +314,5 @@ (let [imported (` ("php constant" (~ (code.text name))))] (in (list (` ((~! syntax:) ((~ (code.local_symbol (maybe.else name alias))) []) (# (~! meta.monad) (~' in) - (list (` (.:as (~ (nullable_type fieldT)) (~ imported)))))))))) + (list (` (.as (~ (nullable_type fieldT)) (~ imported)))))))))) ))) diff --git a/stdlib/source/library/lux/ffi.scm.lux b/stdlib/source/library/lux/ffi.scm.lux index 8beef44d5..93fe11d15 100644 --- a/stdlib/source/library/lux/ffi.scm.lux +++ b/stdlib/source/library/lux/ffi.scm.lux @@ -1,27 +1,27 @@ (.using - [library - [lux {"-" Alias} - ["@" target] - ["[0]" meta] - [abstract - [monad {"+" do}]] - [control - ["[0]" io] - ["[0]" maybe] - ["<>" parser ("[1]#[0]" monad) - ["<[0]>" code {"+" Parser}]]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [type - abstract] - [macro {"+" with_symbols} - [syntax {"+" syntax:}] - ["[0]" code] - ["[0]" template]]]]) + [library + [lux {"-" Alias} + ["@" target] + ["[0]" meta] + [abstract + [monad {"+" do}]] + [control + ["[0]" io] + ["[0]" maybe] + ["<>" parser ("[1]#[0]" monad) + ["<[0]>" code {"+" Parser}]]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [type + abstract] + [macro {"+" with_symbols} + [syntax {"+" syntax:}] + ["[0]" code] + ["[0]" template]]]]) (abstract: .public (Object brand) Any) @@ -193,12 +193,12 @@ (~ (|> (nilable_type outputT) (try_type try?) (io_type io?)))) - (:expected + (as_expected (~ (<| (with_io io?) (with_try try?) (without_nil g!temp outputT) (` ("scheme apply" - (:as ..Function (~ source)) + (as ..Function (~ source)) (~+ (list#each (with_nil g!temp) g!inputs))))))))))) (syntax: .public (import: [import ..import]) @@ -218,5 +218,5 @@ (let [imported (` ("scheme constant" (~ (code.text name))))] (in (list (` ((~! syntax:) ((~ (code.local_symbol (maybe.else name alias)))) (# (~! meta.monad) (~' in) - (list (` (.:as (~ (nilable_type fieldT)) (~ imported)))))))))) + (list (` (.as (~ (nilable_type fieldT)) (~ imported)))))))))) ))) diff --git a/stdlib/source/library/lux/ffi/export.jvm.lux b/stdlib/source/library/lux/ffi/export.jvm.lux index 7473ae233..3368f1671 100644 --- a/stdlib/source/library/lux/ffi/export.jvm.lux +++ b/stdlib/source/library/lux/ffi/export.jvm.lux @@ -66,15 +66,15 @@ (syntax: .public (export: [api <code>.local_symbol exports (<>.many ..export)]) - (let [initialization (: (List (API Constant)) - (list.all (.function (_ it) - (case it - {#Constant it} - {.#Some it} - - _ - {.#None})) - exports))] + (let [initialization (is (List (API Constant)) + (list.all (.function (_ it) + (case it + {#Constant it} + {.#Some it} + + _ + {.#None})) + exports))] (in (list (` (//.class: "final" (~ (code.local_symbol api)) (~+ (list#each (.function (_ it) (case it diff --git a/stdlib/source/library/lux/locale.lux b/stdlib/source/library/lux/locale.lux index 89d77b0e7..59b9e26e6 100644 --- a/stdlib/source/library/lux/locale.lux +++ b/stdlib/source/library/lux/locale.lux @@ -1,20 +1,20 @@ (.using - [library - [lux "*" - [abstract - [equivalence {"+" Equivalence}] - ["[0]" hash {"+" Hash}]] - [control - ["[0]" maybe ("[1]#[0]" functor)]] - [data - ["[0]" text - ["%" format {"+" format}] - ["[0]" encoding {"+" Encoding}]]] - [type - abstract]]] - [/ - ["[0]" language {"+" Language}] - ["[0]" territory {"+" Territory}]]) + [library + [lux "*" + [abstract + [equivalence {"+" Equivalence}] + ["[0]" hash {"+" Hash}]] + [control + ["[0]" maybe ("[1]#[0]" functor)]] + [data + ["[0]" text + ["%" format {"+" format}] + ["[0]" encoding {"+" Encoding}]]] + [type + [abstract {"-" pattern}]]]] + [/ + ["[0]" language {"+" Language}] + ["[0]" territory {"+" Territory}]]) (abstract: .public Locale Text @@ -24,17 +24,17 @@ (def: .public (locale language territory encoding) (-> Language (Maybe Territory) (Maybe Encoding) Locale) - (:abstraction (format (language.code language) - (|> territory - (maybe#each (|>> territory.long_code (format ..territory_separator))) - (maybe.else "")) - (|> encoding - (maybe#each (|>> encoding.name (format ..encoding_separator))) - (maybe.else ""))))) + (abstraction (format (language.code language) + (|> territory + (maybe#each (|>> territory.long_code (format ..territory_separator))) + (maybe.else "")) + (|> encoding + (maybe#each (|>> encoding.name (format ..encoding_separator))) + (maybe.else ""))))) (def: .public code (-> Locale Text) - (|>> :representation)) + (|>> representation)) (def: .public hash (Hash Locale) diff --git a/stdlib/source/library/lux/locale/language.lux b/stdlib/source/library/lux/locale/language.lux index 50604e065..3685740da 100644 --- a/stdlib/source/library/lux/locale/language.lux +++ b/stdlib/source/library/lux/locale/language.lux @@ -7,7 +7,7 @@ [data ["[0]" text]] [type - abstract] + [abstract {"-" pattern}]] [macro ["[0]" template]]]]) @@ -20,7 +20,7 @@ (template [<name> <tag>] [(def: .public <name> (-> Language Text) - (|>> :representation (the <tag>)))] + (|>> representation (the <tag>)))] [name #name] [code #code] @@ -31,8 +31,8 @@ (template [<code> <name> <definition> <alias>+] [(def: .public <definition> Language - (:abstraction [#name <name> - #code <code>])) + (abstraction [#name <name> + #code <code>])) (`` (template [<alias>] [(def: .public <alias> Language diff --git a/stdlib/source/library/lux/locale/territory.lux b/stdlib/source/library/lux/locale/territory.lux index 8df6f861d..dcbf207e7 100644 --- a/stdlib/source/library/lux/locale/territory.lux +++ b/stdlib/source/library/lux/locale/territory.lux @@ -7,7 +7,7 @@ [data ["[0]" text]] [type - abstract] + [abstract {"-" pattern}]] [macro ["[0]" template]]]]) @@ -22,7 +22,7 @@ (template [<name> <field> <type>] [(def: .public <name> (-> Territory <type>) - (|>> :representation + (|>> representation (the <field>)))] [name #name Text] @@ -34,10 +34,10 @@ (template [<short> <long> <number> <name> <main> <neighbor>+] [(def: .public <main> Territory - (:abstraction [#name <name> - #short <short> - #long <long> - #code <number>])) + (abstraction [#name <name> + #short <short> + #long <long> + #code <number>])) (`` (template [<neighbor>] [(def: .public <neighbor> Territory <main>)] @@ -307,7 +307,7 @@ (def: &equivalence ..equivalence) (def: hash - (|>> :representation + (|>> representation (the #long) (# text.hash hash)))) ) diff --git a/stdlib/source/library/lux/macro.lux b/stdlib/source/library/lux/macro.lux index 60df4a57f..eb8fd2531 100644 --- a/stdlib/source/library/lux/macro.lux +++ b/stdlib/source/library/lux/macro.lux @@ -26,7 +26,7 @@ [?macro (//.macro name)] (case ?macro {.#Some macro} - ((:as Macro' macro) args) + ((as Macro' macro) args) {.#None} (# //.monad in (list syntax)))) @@ -43,7 +43,7 @@ (case ?macro {.#Some macro} (do [! //.monad] - [top_level_expansion ((:as Macro' macro) args)] + [top_level_expansion ((as Macro' macro) args)] (|> top_level_expansion (monad.each //.monad expansion) (# ! each list#conjoint))) @@ -63,7 +63,7 @@ (case ?macro {.#Some macro} (do //.monad - [expansion ((:as Macro' macro) args) + [expansion ((as Macro' macro) args) expansion' (monad.each //.monad full_expansion expansion)] (in (list#conjoint expansion'))) @@ -76,7 +76,7 @@ (do //.monad [harg+ (full_expansion harg) targs+ (monad.each //.monad full_expansion targs)] - (in (list (code.form (list#composite harg+ (list#conjoint (: (List (List Code)) targs+))))))) + (in (list (code.form (list#composite harg+ (list#conjoint (is (List (List Code)) targs+))))))) [_ {.#Variant members}] (do //.monad @@ -120,8 +120,8 @@ (pattern (list [_ {.#Tuple symbols}] body)) (do [! //.monad] [symbol_names (monad.each ! ..local_symbol symbols) - .let [symbol_defs (list#conjoint (list#each (: (-> Text (List Code)) - (function (_ name) (list (code.symbol ["" name]) (` (..symbol (~ (code.text name))))))) + .let [symbol_defs (list#conjoint (list#each (is (-> Text (List Code)) + (function (_ name) (list (code.symbol ["" name]) (` (..symbol (~ (code.text name))))))) symbol_names))]] (in (list (` ((~! do) (~! //.monad) [(~+ symbol_defs)] @@ -146,17 +146,17 @@ (let [[module _] (.symbol .._) [_ short] (.symbol <macro>) macro_name [module short]] - (case (: (Maybe [Bit Code]) - (case tokens - (pattern (list [_ {.#Text "omit"}] - token)) - {.#Some [#1 token]} + (case (is (Maybe [Bit Code]) + (case tokens + (pattern (list [_ {.#Text "omit"}] + token)) + {.#Some [#1 token]} - (pattern (list token)) - {.#Some [#0 token]} + (pattern (list token)) + {.#Some [#0 token]} - _ - {.#None})) + _ + {.#None})) {.#Some [omit? token]} (do //.monad [location //.location diff --git a/stdlib/source/library/lux/macro/local.lux b/stdlib/source/library/lux/macro/local.lux index 0e9bd029b..f1060fed1 100644 --- a/stdlib/source/library/lux/macro/local.lux +++ b/stdlib/source/library/lux/macro/local.lux @@ -52,9 +52,9 @@ (-> [Symbol Macro] (Meta Any)) (do meta.monad [[module_name definition_name] (meta.normal name) - .let [definition (: Global {.#Definition [false .Macro macro]}) - add_macro! (: (-> (PList Global) (PList Global)) - (plist.has definition_name definition))]] + .let [definition (is Global {.#Definition [false .Macro macro]}) + add_macro! (is (-> (PList Global) (PList Global)) + (plist.has definition_name definition))]] (..with_module module_name (function (_ module) (case (|> module (the .#definitions) (plist.value definition_name)) @@ -69,8 +69,8 @@ (-> Symbol (Meta Any)) (do meta.monad [[module_name definition_name] (meta.normal name) - .let [lacks_macro! (: (-> (PList Global) (PList Global)) - (plist.lacks definition_name))]] + .let [lacks_macro! (is (-> (PList Global) (PList Global)) + (plist.lacks definition_name))]] (..with_module module_name (function (_ module) (case (|> module (the .#definitions) (plist.value definition_name)) @@ -102,7 +102,7 @@ [_ (monad.each meta.monad ..push_one macros) seed meta.seed g!pop (//.symbol "pop") - _ (let [g!pop (: Symbol - ["" (//code.format g!pop)])] + _ (let [g!pop (is Symbol + ["" (//code.format g!pop)])] (..push_one [g!pop (..pop_all (list#each product.left macros) g!pop)]))] (in (` ((~ g!pop)))))) diff --git a/stdlib/source/library/lux/macro/pattern.lux b/stdlib/source/library/lux/macro/pattern.lux index b789e1f19..1b237996e 100644 --- a/stdlib/source/library/lux/macro/pattern.lux +++ b/stdlib/source/library/lux/macro/pattern.lux @@ -89,20 +89,20 @@ [_ {.#Tuple templates}])}] [_ {.#Form data}] branches)) - (case (: (Maybe (List Code)) - (do maybe_monad - [bindings' (monad#each maybe_monad symbol_short bindings) - data' (monad#each maybe_monad tuple_list data)] - (.let [num_bindings (list#size bindings')] - (if (every? (|>> ("lux i64 =" num_bindings)) - (list#each list#size data')) - (.let [apply (: (-> Replacement_Environment (List Code)) - (function (_ env) (list#each (realized_template env) templates)))] - (.|> data' - (list#each (function#composite apply (replacement_environment bindings'))) - list#conjoint - in)) - {.#None})))) + (case (is (Maybe (List Code)) + (do maybe_monad + [bindings' (monad#each maybe_monad symbol_short bindings) + data' (monad#each maybe_monad tuple_list data)] + (.let [num_bindings (list#size bindings')] + (if (every? (|>> ("lux i64 =" num_bindings)) + (list#each list#size data')) + (.let [apply (is (-> Replacement_Environment (List Code)) + (function (_ env) (list#each (realized_template env) templates)))] + (.|> data' + (list#each (function#composite apply (replacement_environment bindings'))) + list#conjoint + in)) + {.#None})))) {.#Some output} (meta#in (list#composite output branches)) diff --git a/stdlib/source/library/lux/macro/syntax.lux b/stdlib/source/library/lux/macro/syntax.lux index 46fb3b98d..8530307be 100644 --- a/stdlib/source/library/lux/macro/syntax.lux +++ b/stdlib/source/library/lux/macro/syntax.lux @@ -1,29 +1,29 @@ (.using - [library - [lux "*" - ["[0]" macro {"+" with_symbols}] - ["[0]" meta] - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" maybe] - ["[0]" try] - ["<>" parser - ["</>" code {"+" Parser}]]] - [data - ["[0]" text ("[1]#[0]" monoid)] - [collection - ["[0]" list]]] - [math - [number - ["[0]" nat] - ["[0]" int] - ["[0]" rev] - ["[0]" frac]]]]] - [// - ["[0]" code]] - ["[0]" / "_" - ["[1][0]" export]]) + [library + [lux "*" + ["[0]" macro {"+" with_symbols}] + ["[0]" meta] + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" maybe] + ["[0]" try] + ["<>" parser + ["</>" code {"+" Parser}]]] + [data + ["[0]" text ("[1]#[0]" monoid)] + [collection + ["[0]" list]]] + [math + [number + ["[0]" nat] + ["[0]" int] + ["[0]" rev] + ["[0]" frac]]]]] + [// + ["[0]" code]] + ["[0]" / "_" + ["[1][0]" export]]) (def: (self_documenting binding parser) (All (_ a) (-> Code (Parser a) (Parser a))) @@ -60,20 +60,20 @@ [vars+parsers (case (list.pairs args) {.#Some args} (monad.each ! - (: (-> [Code Code] (Meta [Code Code])) - (function (_ [var parser]) - (with_expansions [<default> (in [var - (` ((~! ..self_documenting) (' (~ var)) - (~ parser)))])] - (case var - [_ {.#Symbol ["" _]}] - <default> + (is (-> [Code Code] (Meta [Code Code])) + (function (_ [var parser]) + (with_expansions [<default> (in [var + (` ((~! ..self_documenting) (' (~ var)) + (~ parser)))])] + (case var + [_ {.#Symbol ["" _]}] + <default> - [_ {.#Symbol _}] - (in [var parser]) + [_ {.#Symbol _}] + (in [var parser]) - _ - <default>)))) + _ + <default>)))) args) _ @@ -83,10 +83,10 @@ error_msg (code.text (macro.wrong_syntax_error [this_module name]))]] (in (list (` (.macro: (~ export_policy) ((~ (code.symbol ["" name])) (~ g!tokens) (~ g!state)) (.case ((~! </>.result) - (: ((~! </>.Parser) (Meta (List Code))) - ((~! do) (~! <>.monad) - [(~+ (..un_paired vars+parsers))] - ((~' in) (~ body)))) + (is ((~! </>.Parser) (Meta (List Code))) + ((~! do) (~! <>.monad) + [(~+ (..un_paired vars+parsers))] + ((~' in) (~ body)))) (~ g!tokens)) {try.#Success (~ g!body)} ((~ g!body) (~ g!state)) diff --git a/stdlib/source/library/lux/macro/template.lux b/stdlib/source/library/lux/macro/template.lux index 247c752c7..d2260f584 100644 --- a/stdlib/source/library/lux/macro/template.lux +++ b/stdlib/source/library/lux/macro/template.lux @@ -136,9 +136,9 @@ (.let [parameters_amount (list.size _#parameters) inputs_amount (list.size inputs)] (if (nat.= parameters_amount inputs_amount) - (.let [environment (: Environment - (|> (list.zipped/2 _#parameters inputs) - (dictionary.of_list text.hash)))] + (.let [environment (is Environment + (|> (list.zipped/2 _#parameters inputs) + (dictionary.of_list text.hash)))] {.#Right [compiler (list#each (..applied environment) _#template)]}) (exception.except ..irregular_arguments [parameters_amount inputs_amount])))))) @@ -156,14 +156,14 @@ body <code>.any]) (do meta.monad [here_name meta.current_module_name - expression? (: (Meta Bit) - (function (_ lux) - {try.#Success [lux (case (the .#expected lux) - {.#None} - false - - {.#Some _} - true)]})) + expression? (is (Meta Bit) + (function (_ lux) + {try.#Success [lux (case (the .#expected lux) + {.#None} + false + + {.#Some _} + true)]})) g!pop (local.push (list#each (function (_ local) [[here_name (the #name local)] (..macro local)]) diff --git a/stdlib/source/library/lux/math/modular.lux b/stdlib/source/library/lux/math/modular.lux index f556c1404..8f4ef73a8 100644 --- a/stdlib/source/library/lux/math/modular.lux +++ b/stdlib/source/library/lux/math/modular.lux @@ -23,7 +23,7 @@ [number ["i" int ("[1]#[0]" decimal)]]] [type - abstract]]] + [abstract {"-" pattern}]]]] ["[0]" // "_" ["[1]" modulus {"+" Modulus}]]) @@ -34,13 +34,13 @@ (def: .public (modular modulus value) (All (_ %) (-> (Modulus %) Int (Mod %))) - (:abstraction [#modulus modulus - #value (i.mod (//.divisor modulus) value)])) + (abstraction [#modulus modulus + #value (i.mod (//.divisor modulus) value)])) (template [<name> <type> <side>] [(def: .public <name> (All (_ %) (-> (Mod %) <type>)) - (|>> :representation <side>))] + (|>> representation <side>))] [modulus (Modulus %) product.left] [value Int product.right] @@ -64,7 +64,7 @@ (All (_ %) (-> (Modulus %) (Codec Text (Mod %)))) (def: (encoded modular) - (let [[_ value] (:representation modular)] + (let [[_ value] (representation modular)] ($_ text#composite (i#encoded value) ..separator @@ -81,8 +81,8 @@ (template [<name> <op>] [(def: .public (<name> reference subject) (All (_ %) (-> (Mod %) (Mod %) Bit)) - (let [[_ reference] (:representation reference) - [_ subject] (:representation subject)] + (let [[_ reference] (representation reference) + [_ subject] (representation subject)] (<op> reference subject)))] [= i.=] @@ -106,12 +106,12 @@ (template [<name> <op>] [(def: .public (<name> param subject) (All (_ %) (-> (Mod %) (Mod %) (Mod %))) - (let [[modulus param] (:representation param) - [_ subject] (:representation subject)] - (:abstraction [#modulus modulus - #value (|> subject - (<op> param) - (i.mod (//.divisor modulus)))])))] + (let [[modulus param] (representation param) + [_ subject] (representation subject)] + (abstraction [#modulus modulus + #value (|> subject + (<op> param) + (i.mod (//.divisor modulus)))])))] [+ i.+] [- i.-] @@ -133,7 +133,7 @@ (def: .public (inverse modular) (All (_ %) (-> (Mod %) (Maybe (Mod %)))) - (let [[modulus value] (:representation modular) + (let [[modulus value] (representation modular) [[vk mk] gcd] (i.extended_gcd value (//.divisor modulus))] (case gcd +1 {.#Some (..modular modulus vk)} diff --git a/stdlib/source/library/lux/math/modulus.lux b/stdlib/source/library/lux/math/modulus.lux index 4a8daaa97..6a08451e1 100644 --- a/stdlib/source/library/lux/math/modulus.lux +++ b/stdlib/source/library/lux/math/modulus.lux @@ -1,22 +1,22 @@ (.using - [library - [lux "*" - ["[0]" meta] - [abstract - [monad {"+" do}]] - [control - ["[0]" try {"+" Try}] - ["[0]" exception {"+" exception:}] - [parser - ["<[0]>" code]]] - [macro - [syntax {"+" syntax:}] - ["[0]" code]] - [math - [number - ["i" int]]] - [type - abstract]]]) + [library + [lux "*" + ["[0]" meta] + [abstract + [monad {"+" do}]] + [control + ["[0]" try {"+" Try}] + ["[0]" exception {"+" exception:}] + [parser + ["<[0]>" code]]] + [macro + [syntax {"+" syntax:}] + ["[0]" code]] + [math + [number + ["i" int]]] + [type + [abstract {"-" pattern}]]]]) (exception: .public zero_cannot_be_a_modulus) @@ -27,22 +27,22 @@ (Ex (_ %) (-> Int (Try (Modulus %)))) (if (i.= +0 value) (exception.except ..zero_cannot_be_a_modulus []) - {try.#Success (:abstraction value)})) + {try.#Success (abstraction value)})) (def: .public divisor (All (_ %) (-> (Modulus %) Int)) - (|>> :representation)) + (|>> representation)) (def: .public (= reference subject) (All (_ %r %s) (-> (Modulus %r) (Modulus %s) Bit)) - (i.= (:representation reference) - (:representation subject))) + (i.= (representation reference) + (representation subject))) (def: .public (congruent? modulus reference subject) (All (_ %) (-> (Modulus %) Int Int Bit)) (|> subject (i.- reference) - (i.% (:representation modulus)) + (i.% (representation modulus)) (i.= +0))) ) diff --git a/stdlib/source/library/lux/math/number/frac.lux b/stdlib/source/library/lux/math/number/frac.lux index 511b0fef9..6d81a958b 100644 --- a/stdlib/source/library/lux/math/number/frac.lux +++ b/stdlib/source/library/lux/math/number/frac.lux @@ -64,14 +64,14 @@ @.jvm (as_is (template: (!double value) [(|> value - (:as (Primitive "java.lang.Double")) + (as (Primitive "java.lang.Double")) "jvm object cast")]) (template: (!frac value) [(|> value "jvm object cast" - (: (Primitive "java.lang.Double")) - (:as Frac))]) + (is (Primitive "java.lang.Double")) + (as Frac))]) (template [<name> <method>] [(def: .public <name> @@ -111,7 +111,7 @@ (-> Frac Frac) (|>> [] ("js apply" ("js constant" <method>)) - (:as Frac)))] + (as Frac)))] [cos "Math.cos"] [sin "Math.sin"] @@ -133,7 +133,7 @@ (def: .public (pow param subject) (-> Frac Frac Frac) - (:as Frac ("js apply" ("js constant" "Math.pow") [subject param])))) + (as Frac ("js apply" ("js constant" "Math.pow") [subject param])))) @.python (as_is (template [<name> <method>] @@ -141,7 +141,7 @@ (-> Frac Frac) (|>> [] ("python object do" <method> ("python import" "math")) - (:as Frac)))] + (as Frac)))] [cos "cos"] [sin "sin"] @@ -162,7 +162,7 @@ (def: .public (pow param subject) (-> Frac Frac Frac) - (:as Frac ("python object do" "pow" ("python import" "math") [subject param]))) + (as Frac ("python object do" "pow" ("python import" "math") [subject param]))) (def: .public (root/3 it) (-> Frac Frac) @@ -180,7 +180,7 @@ (-> Frac Frac) (|>> [] ("lua apply" ("lua constant" <method>)) - (:as Frac)))] + (as Frac)))] [cos "math.cos"] [sin "math.sin"] @@ -219,7 +219,7 @@ (-> Frac Frac) (|>> [] ("ruby apply" ("ruby constant" <method>)) - (:as Frac)))] + (as Frac)))] [cos "Math.cos"] [sin "Math.sin"] @@ -240,7 +240,7 @@ [(def: .public (<name> it) (-> Frac Frac) (|> ("ruby object do" <method> it []) - (:as Int) + (as Int) ("lux i64 f64")))] [ceil "ceil"] @@ -249,14 +249,14 @@ (def: .public (pow param subject) (-> Frac Frac Frac) - (:as Frac ("ruby object do" "**" subject [param])))) + (as Frac ("ruby object do" "**" subject [param])))) @.php (as_is (template [<name> <method>] [(def: .public <name> (-> Frac Frac) (|>> ("php apply" ("php constant" <method>)) - (:as Frac)))] + (as Frac)))] [cos "cos"] [sin "sin"] @@ -277,7 +277,7 @@ (def: .public (pow param subject) (-> Frac Frac Frac) - (:as Frac ("php apply" ("php constant" "pow") subject param))) + (as Frac ("php apply" ("php constant" "pow") subject param))) (def: .public root/3 (-> Frac Frac) @@ -288,7 +288,7 @@ [(def: .public <name> (-> Frac Frac) (|>> ("scheme apply" ("scheme constant" <method>)) - (:as Frac)))] + (as Frac)))] [cos "cos"] [sin "sin"] @@ -309,7 +309,7 @@ (def: .public (pow param subject) (-> Frac Frac Frac) - (:as Frac ("scheme apply" ("scheme constant" "expt") subject param))) + (as Frac ("scheme apply" ("scheme constant" "expt") subject param))) (def: .public root/3 (-> Frac Frac) @@ -713,9 +713,9 @@ (def: .public (of_bits it) (-> I64 Frac) - (case [(: Nat (..exponent it)) - (: Nat (..mantissa it)) - (: Nat (..sign it))] + (case [(is Nat (..exponent it)) + (is Nat (..mantissa it)) + (is Nat (..sign it))] (pattern [(static ..special_exponent_bits) 0 0]) ..positive_infinity diff --git a/stdlib/source/library/lux/math/number/i16.lux b/stdlib/source/library/lux/math/number/i16.lux index 467fa363f..06a52afa5 100644 --- a/stdlib/source/library/lux/math/number/i16.lux +++ b/stdlib/source/library/lux/math/number/i16.lux @@ -1,24 +1,32 @@ (.using - [library - [lux {"-" i64} - [abstract - [equivalence {"+" Equivalence}]] - [control - ["[0]" maybe]] - [type {"+" :by_example}]]] - [// - ["[0]" i64 {"+" Sub}]]) + [library + [lux {"-" i64} + [abstract + [equivalence {"+" Equivalence}]] + [control + ["[0]" maybe]] + [type {"+" by_example}]]] + [// + ["[0]" i64 {"+" Sub}]]) (def: sub (maybe.trusted (i64.sub 16))) (def: .public I16 Type - (:by_example [size] - (Sub size) - ..sub - - (I64 size))) + ... TODO: Switch to the cleaner approach ASAP. + (case (type_of ..sub) + {.#Apply :size: :sub:} + (type (I64 :size:)) + + _ + (undefined)) + ... (by_example [size] + ... (Sub size) + ... ..sub + + ... (I64 size)) + ) (def: .public equivalence (Equivalence I16) (# ..sub &equivalence)) (def: .public width Nat (# ..sub bits)) diff --git a/stdlib/source/library/lux/math/number/i32.lux b/stdlib/source/library/lux/math/number/i32.lux index e8967c412..6ddbcf015 100644 --- a/stdlib/source/library/lux/math/number/i32.lux +++ b/stdlib/source/library/lux/math/number/i32.lux @@ -1,7 +1,7 @@ (.using [library [lux {"-" i64} - [type {"+" :by_example}] + [type {"+" by_example}] [abstract [equivalence {"+" Equivalence}]] [control @@ -11,16 +11,24 @@ (def: sub ... TODO: Stop needing this coercion. - (:as (Sub (I64 (Primitive "#I32"))) - (maybe.trusted (i64.sub 32)))) + (as (Sub (I64 (Primitive "#I32"))) + (maybe.trusted (i64.sub 32)))) (def: .public I32 Type - (:by_example [size] - (Sub size) - ..sub - - (I64 size))) + ... TODO: Switch to the cleaner approach ASAP. + (case (type_of ..sub) + {.#Apply :size: :sub:} + (type (I64 :size:)) + + _ + (undefined)) + ... (by_example [size] + ... (Sub size) + ... ..sub + + ... (I64 size)) + ) (def: .public equivalence (Equivalence I32) (# ..sub &equivalence)) (def: .public width Nat (# ..sub bits)) diff --git a/stdlib/source/library/lux/math/number/i64.lux b/stdlib/source/library/lux/math/number/i64.lux index 281ea025e..3dcd42f8b 100644 --- a/stdlib/source/library/lux/math/number/i64.lux +++ b/stdlib/source/library/lux/math/number/i64.lux @@ -1,14 +1,14 @@ (.using - [library - [lux {"-" and or not false true} - [abstract - [equivalence {"+" Equivalence}] - [hash {"+" Hash}] - [monoid {"+" Monoid}]] - [control - ["[0]" try]]]] - [// - ["n" nat]]) + [library + [lux {"-" and or not false true} + [abstract + [equivalence {"+" Equivalence}] + [hash {"+" Hash}] + [monoid {"+" Monoid}]] + [control + ["[0]" try]]]] + [// + ["n" nat]]) (def: .public bits_per_byte 8) @@ -97,7 +97,7 @@ (def: .public (one? index input) (-> Nat (I64 Any) Bit) - (|> input (:as I64) (..and (..bit index)) (n.= 0) .not)) + (|> input .i64 (..and (..bit index)) (n.= 0) .not)) (def: .public (zero? index input) (-> Nat (I64 Any) Bit) @@ -143,27 +143,27 @@ (def: .public reversed (All (_ a) (-> (I64 a) (I64 a))) - (let [swapper (: (-> Nat (All (_ a) (-> (I64 a) (I64 a)))) - (function (_ power) - (let [size (..left_shifted power 1) - repetitions (: (-> Nat Text Text) - (function (_ times char) - (loop [iterations 1 - output char] - (if (n.< times iterations) - (again (++ iterations) - ("lux text concat" char output)) - output)))) - pattern (repetitions (n./ (n.+ size size) ..width) - ("lux text concat" - (repetitions size "1") - (repetitions size "0"))) - - high (try.trusted (# n.binary decoded pattern)) - low (..right_rotated size high)] - (function (_ value) - (..or (..right_shifted size (..and high value)) - (..left_shifted size (..and low value))))))) + (let [swapper (is (-> Nat (All (_ a) (-> (I64 a) (I64 a)))) + (function (_ power) + (let [size (..left_shifted power 1) + repetitions (is (-> Nat Text Text) + (function (_ times char) + (loop [iterations 1 + output char] + (if (n.< times iterations) + (again (++ iterations) + ("lux text concat" char output)) + output)))) + pattern (repetitions (n./ (n.+ size size) ..width) + ("lux text concat" + (repetitions size "1") + (repetitions size "0"))) + + high (try.trusted (# n.binary decoded pattern)) + low (..right_rotated size high)] + (function (_ value) + (..or (..right_shifted size (..and high value)) + (..left_shifted size (..and low value))))))) swap/01 (swapper 0) swap/02 (swapper 1) @@ -180,14 +180,14 @@ (type: .public (Sub size) (Interface - (: (Equivalence (I64 size)) - &equivalence) - (: Nat - bits) - (: (-> I64 (I64 size)) - narrow) - (: (-> (I64 size) I64) - wide))) + (is (Equivalence (I64 size)) + &equivalence) + (is Nat + bits) + (is (-> I64 (I64 size)) + narrow) + (is (-> (I64 size) I64) + wide))) (def: .public (sub width) (Ex (_ size) (-> Nat (Maybe (Sub size)))) @@ -197,15 +197,15 @@ sign (..bit (-- width)) mantissa (..mask (-- width)) co_mantissa (..xor (.i64 -1) mantissa)] - {.#Some (: Sub - (implementation - (def: &equivalence ..equivalence) - (def: bits width) - (def: (narrow value) - (..or (|> value (..and ..sign) (..right_shifted sign_shift)) - (|> value (..and mantissa)))) - (def: (wide value) - (.i64 (case (.nat (..and sign value)) - 0 value - _ (..or co_mantissa value))))))}) + {.#Some (is Sub + (implementation + (def: &equivalence ..equivalence) + (def: bits width) + (def: (narrow value) + (..or (|> value (..and ..sign) (..right_shifted sign_shift)) + (|> value (..and mantissa)))) + (def: (wide value) + (.i64 (case (.nat (..and sign value)) + 0 value + _ (..or co_mantissa value))))))}) {.#None})) diff --git a/stdlib/source/library/lux/math/number/i8.lux b/stdlib/source/library/lux/math/number/i8.lux index 469796261..15dc8c13a 100644 --- a/stdlib/source/library/lux/math/number/i8.lux +++ b/stdlib/source/library/lux/math/number/i8.lux @@ -1,24 +1,32 @@ (.using - [library - [lux {"-" i64} - [abstract - [equivalence {"+" Equivalence}]] - [control - ["[0]" maybe]] - [type {"+" :by_example}]]] - [// - ["[0]" i64 {"+" Sub}]]) + [library + [lux {"-" i64} + [type {"+" by_example}] + [abstract + [equivalence {"+" Equivalence}]] + [control + ["[0]" maybe]]]] + [// + ["[0]" i64 {"+" Sub}]]) (def: sub (maybe.trusted (i64.sub 8))) (def: .public I8 Type - (:by_example [size] - (Sub size) - ..sub - - (I64 size))) + ... TODO: Switch to the cleaner approach ASAP. + (case (type_of ..sub) + {.#Apply :size: :sub:} + (type (I64 :size:)) + + _ + (undefined)) + ... (by_example [size] + ... (Sub size) + ... ..sub + + ... (I64 size)) + ) (def: .public equivalence (Equivalence I8) (# ..sub &equivalence)) (def: .public width Nat (# ..sub bits)) diff --git a/stdlib/source/library/lux/math/number/nat.lux b/stdlib/source/library/lux/math/number/nat.lux index 9ead2ee82..31537c887 100644 --- a/stdlib/source/library/lux/math/number/nat.lux +++ b/stdlib/source/library/lux/math/number/nat.lux @@ -74,24 +74,23 @@ (def: .public (* parameter subject) (-> Nat Nat Nat) - (:as Nat - ("lux i64 *" - (:as Int parameter) - (:as Int subject)))) + (.nat ("lux i64 *" + (.int parameter) + (.int subject)))) (def: .public (/ parameter subject) (-> Nat Nat Nat) - (if ("lux i64 <" +0 (:as Int parameter)) + (if ("lux i64 <" +0 (.int parameter)) (if (..< parameter subject) 0 1) (let [quotient (|> subject ("lux i64 right-shift" 1) - ("lux i64 /" (:as Int parameter)) + ("lux i64 /" (.int parameter)) ("lux i64 left-shift" 1)) flat ("lux i64 *" - (:as Int parameter) - (:as Int quotient)) + (.int parameter) + (.int quotient)) remainder ("lux i64 -" flat subject)] (if (..< parameter remainder) quotient @@ -101,15 +100,15 @@ (-> Nat Nat [Nat Nat]) (let [quotient (../ parameter subject) flat ("lux i64 *" - (:as Int parameter) - (:as Int quotient))] + (.int parameter) + (.int quotient))] [quotient ("lux i64 -" flat subject)])) (def: .public (% parameter subject) (-> Nat Nat Nat) (let [flat ("lux i64 *" - (:as Int parameter) - (:as Int (../ parameter subject)))] + (.int parameter) + (.int (../ parameter subject)))] ("lux i64 -" flat subject))) (def: .public (gcd a b) @@ -298,7 +297,7 @@ (let [output' ("lux text concat" (<to_character> ("lux i64 and" mask input)) output)] - (case (: Nat ("lux i64 right-shift" <shift> input)) + (case (is Nat ("lux i64 right-shift" <shift> input)) 0 output' diff --git a/stdlib/source/library/lux/math/number/rev.lux b/stdlib/source/library/lux/math/number/rev.lux index f00cc8dd7..9a6e9c826 100644 --- a/stdlib/source/library/lux/math/number/rev.lux +++ b/stdlib/source/library/lux/math/number/rev.lux @@ -127,7 +127,7 @@ (with_expansions [<least_significant_bit> 1] (def: .public (reciprocal numerator) (-> Nat Rev) - (.rev (case (: Nat ("lux i64 and" <least_significant_bit> numerator)) + (.rev (case (is Nat ("lux i64 and" <least_significant_bit> numerator)) 0 (..even_reciprocal numerator) _ (..odd_reciprocal numerator)))) @@ -135,7 +135,7 @@ (-> Rev Rev Rev) (if ("lux i64 =" +0 param) (panic! "Cannot divide Rev by zero!") - (let [reciprocal (case (: Nat ("lux i64 and" <least_significant_bit> param)) + (let [reciprocal (case (is Nat ("lux i64 and" <least_significant_bit> param)) 0 (..even_reciprocal (.nat param)) _ (..odd_reciprocal (.nat param)))] (.rev (//nat.* reciprocal (.nat subject))))))) @@ -234,13 +234,13 @@ 0 0 _ 1)) raw_size ("lux text size" raw_output) - zero_padding (: Text - (loop [zeroes_left (: Nat (//nat.- raw_size max_num_chars)) - output (: Text "")] - (if (//nat.= 0 zeroes_left) - output - (again (-- zeroes_left) - ("lux text concat" "0" output)))))] + zero_padding (is Text + (loop [zeroes_left (is Nat (//nat.- raw_size max_num_chars)) + output (is Text "")] + (if (//nat.= 0 zeroes_left) + output + (again (-- zeroes_left) + ("lux text concat" "0" output)))))] (|> raw_output ("lux text concat" zero_padding) ("lux text concat" ".")))) diff --git a/stdlib/source/library/lux/math/random.lux b/stdlib/source/library/lux/math/random.lux index 2d21ae951..c172e5c98 100644 --- a/stdlib/source/library/lux/math/random.lux +++ b/stdlib/source/library/lux/math/random.lux @@ -152,8 +152,8 @@ (let [start (unicode.start set) end (unicode.end set) size (n.- start end) - in_range (: (-> Char Char) - (|>> (n.% size) (n.+ start)))] + in_range (is (-> Char Char) + (|>> (n.% size) (n.+ start)))] (|> ..nat (# ..functor each in_range) (..only (unicode.member? set))))) @@ -375,10 +375,10 @@ ... http://xorshift.di.unimi.it/splitmix64.c (def: .public split_mix_64 (-> Nat PRNG) - (let [twist (: (-> Nat Nat Nat) - (function (_ shift value) - (i64.xor (i64.right_shifted shift value) - value))) + (let [twist (is (-> Nat Nat Nat) + (function (_ shift value) + (i64.xor (i64.right_shifted shift value) + value))) mix n.*] (..prng (n.+ (hex "9E,37,79,B9,7F,4A,7C,15")) (|>> (twist 30) diff --git a/stdlib/source/library/lux/meta.lux b/stdlib/source/library/lux/meta.lux index 6b78550a3..e349785f3 100644 --- a/stdlib/source/library/lux/meta.lux +++ b/stdlib/source/library/lux/meta.lux @@ -166,41 +166,41 @@ (-> Symbol (Meta (Maybe Macro))) (do ..monad [[module name] (..normal full_name)] - (: (Meta (Maybe Macro)) - (function (_ lux) - {try.#Success [lux - (case (..current_module_name lux) - {try.#Failure error} - {.#None} - - {try.#Success [_ this_module]} - (let [modules (the .#modules lux)] - (loop [module module - name name] - (do maybe.monad - [$module (plist.value module modules) - definition (: (Maybe Global) - (|> $module - (: Module) - (the .#definitions) - (plist.value name)))] - (case definition - {.#Alias [r_module r_name]} - (again r_module r_name) - - {.#Definition [exported? def_type def_value]} - (if (macro_type? def_type) - {.#Some (:as Macro def_value)} - {.#None}) - - {.#Type [exported? type labels]} - {.#None} - - {.#Tag _} - {.#None} - - {.#Slot _} - {.#None})))))]})))) + (is (Meta (Maybe Macro)) + (function (_ lux) + {try.#Success [lux + (case (..current_module_name lux) + {try.#Failure error} + {.#None} + + {try.#Success [_ this_module]} + (let [modules (the .#modules lux)] + (loop [module module + name name] + (do maybe.monad + [$module (plist.value module modules) + definition (is (Maybe Global) + (|> $module + (is Module) + (the .#definitions) + (plist.value name)))] + (case definition + {.#Alias [r_module r_name]} + (again r_module r_name) + + {.#Definition [exported? def_type def_value]} + (if (macro_type? def_type) + {.#Some (as Macro def_value)} + {.#None}) + + {.#Type [exported? type labels]} + {.#None} + + {.#Tag _} + {.#None} + + {.#Slot _} + {.#None})))))]})))) (def: .public seed (Meta Nat) @@ -256,20 +256,20 @@ (def: .public (var_type name) (-> Text (Meta Type)) (function (_ lux) - (let [test (: (-> [Text [Type Any]] Bit) - (|>> product.left (text#= name)))] + (let [test (is (-> [Text [Type Any]] Bit) + (|>> product.left (text#= name)))] (case (do maybe.monad [scope (list.example (function (_ env) - (or (list.any? test (: (List [Text [Type Any]]) - (the [.#locals .#mappings] env))) - (list.any? test (: (List [Text [Type Any]]) - (the [.#captured .#mappings] env))))) + (or (list.any? test (is (List [Text [Type Any]]) + (the [.#locals .#mappings] env))) + (list.any? test (is (List [Text [Type Any]]) + (the [.#captured .#mappings] env))))) (the .#scopes lux)) [_ [type _]] (on_either (list.example test) - (: (List [Text [Type Any]]) - (the [.#locals .#mappings] scope)) - (: (List [Text [Type Any]]) - (the [.#captured .#mappings] scope)))] + (is (List [Text [Type Any]]) + (the [.#locals .#mappings] scope)) + (is (List [Text [Type Any]]) + (the [.#captured .#mappings] scope)))] (in type)) {.#Some var_type} ((clean_type var_type) lux) @@ -299,12 +299,12 @@ [name (..normal name) .let [[normal_module normal_short] name]] (function (_ lux) - (case (: (Maybe Global) - (do maybe.monad - [(open "[0]") (|> lux - (the .#modules) - (plist.value normal_module))] - (plist.value normal_short #definitions))) + (case (is (Maybe Global) + (do maybe.monad + [(open "[0]") (|> lux + (the .#modules) + (plist.value normal_module))] + (plist.value normal_short #definitions))) {.#Some definition} {try.#Success [lux definition]} @@ -440,7 +440,7 @@ (# code.equivalence = (type_code .Type) (type_code def_type))) - (in (:as Type def_value)) + (in (as Type def_value)) (..failure ($_ text#composite "Definition is not a type: " (symbol#encoded name))))) {.#Type [exported? type labels]} diff --git a/stdlib/source/library/lux/meta/configuration.lux b/stdlib/source/library/lux/meta/configuration.lux index 372189c39..54bb66630 100644 --- a/stdlib/source/library/lux/meta/configuration.lux +++ b/stdlib/source/library/lux/meta/configuration.lux @@ -61,10 +61,10 @@ (def: .public parser (Parser Configuration) - (let [parser' (: (Parser Text) - (<| (<>.after (<text>.this ..start)) - (<>.before (<text>.this ..end)) - (<text>.slice (<text>.some! (<text>.none_of! ..end)))))] + (let [parser' (is (Parser Text) + (<| (<>.after (<text>.this ..start)) + (<>.before (<text>.this ..end)) + (<text>.slice (<text>.some! (<text>.none_of! ..end)))))] (<>.some (<>.and parser' parser')))) (exception: .public invalid) diff --git a/stdlib/source/library/lux/meta/location.lux b/stdlib/source/library/lux/meta/location.lux index 1080669a2..b1448bf9e 100644 --- a/stdlib/source/library/lux/meta/location.lux +++ b/stdlib/source/library/lux/meta/location.lux @@ -23,10 +23,10 @@ {.#End} (let [location (the .#location compiler)] {.#Right [compiler - (list (` (.: .Location - [.#module (~ [..dummy {.#Text (the .#module location)}]) - .#line (~ [..dummy {.#Nat (the .#line location)}]) - .#column (~ [..dummy {.#Nat (the .#column location)}])])))]}) + (list (` (.is .Location + [.#module (~ [..dummy {.#Text (the .#module location)}]) + .#line (~ [..dummy {.#Nat (the .#line location)}]) + .#column (~ [..dummy {.#Nat (the .#column location)}])])))]}) _ {.#Left (`` (("lux in-module" (~~ (static .prelude_module)) wrong_syntax_error) (symbol ..here)))})) diff --git a/stdlib/source/library/lux/program.lux b/stdlib/source/library/lux/program.lux index 253bf9b54..4b25a55b2 100644 --- a/stdlib/source/library/lux/program.lux +++ b/stdlib/source/library/lux/program.lux @@ -44,11 +44,11 @@ {#Parsed args} (` (.function ((~ g!program) (~ g!args)) - (case ((~! <cli>.result) (: (~! (<cli>.Parser (io.IO .Any))) - ((~! do) (~! <>.monad) - [(~+ args) - (~ g!_) (~! <cli>.end)] - ((~' in) (~ initialization+event_loop)))) + (case ((~! <cli>.result) (.is (~! (<cli>.Parser (io.IO .Any))) + ((~! do) (~! <>.monad) + [(~+ args) + (~ g!_) (~! <cli>.end)] + ((~' in) (~ initialization+event_loop)))) (~ g!args)) {.#Right (~ g!output)} (~ g!output) diff --git a/stdlib/source/library/lux/static.lux b/stdlib/source/library/lux/static.lux index e4ccd2c3c..3f1e535ad 100644 --- a/stdlib/source/library/lux/static.lux +++ b/stdlib/source/library/lux/static.lux @@ -20,7 +20,7 @@ (template [<name> <type> <format>] [(syntax: .public (<name> [expression <code>.any]) (# meta.monad each - (|>> (:as <type>) <format> list) + (|>> (as <type>) <format> list) (meta.eval <type> expression)))] [bit .Bit code.bit] @@ -43,7 +43,7 @@ (do meta.monad [pair (meta.eval (.type <type>) (` [(~ format) (~ expression)])) - .let [[format expression] (:as <type> pair)]] + .let [[format expression] (as <type> pair)]] (in (list (format expression)))))) (with_expansions [<type> (Ex (_ a) @@ -54,7 +54,7 @@ (do meta.monad [pair (meta.eval (.type <type>) (` [(~ format) (~ expression)])) - .let [[format expression] (:as <type> pair)]] + .let [[format expression] (as <type> pair)]] (in (list#each format expression))))) (syntax: .public (seed []) @@ -83,7 +83,7 @@ (do meta.monad [pair (meta.eval (type <type>) (` [(~ format) (~ random)])) - .let [[format random] (:as <type> pair)] + .let [[format random] (as <type> pair)] seed meta.seed .let [[_ result] (random.result (random.pcg_32 [..pcg_32_magic_inc seed]) random)]] @@ -97,7 +97,7 @@ (do meta.monad [pair (meta.eval (type <type>) (` [(~ format) (~ random)])) - .let [[format random] (:as <type> pair)] + .let [[format random] (as <type> pair)] seed meta.seed .let [[_ result] (random.result (random.pcg_32 [..pcg_32_magic_inc seed]) random)]] @@ -108,7 +108,7 @@ else <code>.any]) (do meta.monad [test (meta.eval .Bit test)] - (in (list (.if (:as .Bit test) + (in (list (.if (as .Bit test) then else))))) @@ -125,6 +125,6 @@ then <code>.any]) (do meta.monad [test (meta.eval .Bit test)] - (in (.if (:as .Bit test) + (in (.if (as .Bit test) (list then) (list))))) diff --git a/stdlib/source/library/lux/target/common_lisp.lux b/stdlib/source/library/lux/target/common_lisp.lux index 6c98c57e0..15d35df29 100644 --- a/stdlib/source/library/lux/target/common_lisp.lux +++ b/stdlib/source/library/lux/target/common_lisp.lux @@ -14,7 +14,7 @@ [number ["f" frac]]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) (def: as_form (-> Text Text) @@ -25,11 +25,11 @@ (def: .public manual (-> Text Code) - (|>> :abstraction)) + (|>> abstraction)) (def: .public code (-> (Code Any) Text) - (|>> :representation)) + (|>> representation)) (template [<type> <super>] [(with_expansions [<brand> (template.symbol [<type> "'"])] @@ -64,12 +64,12 @@ (def: .public nil Literal - (:abstraction "()")) + (abstraction "()")) (template [<prefix> <name>] [(def: .public <name> (-> Text Literal) - (|>> (format <prefix>) :abstraction))] + (|>> (format <prefix>) abstraction))] ["'" symbol] [":" keyword]) @@ -82,7 +82,7 @@ (def: .public int (-> Int Literal) - (|>> %.int :abstraction)) + (|>> %.int abstraction)) (def: .public float (-> Frac Literal) @@ -97,11 +97,11 @@ ... else [%.frac]) - :abstraction)) + abstraction)) (def: .public (double value) (-> Frac Literal) - (:abstraction + (abstraction (.cond (f.= f.positive_infinity value) "(/ 1.0d0 0.0d0)" @@ -138,18 +138,18 @@ (-> Text Literal) (|>> ..safe (text.enclosed' text.double_quote) - :abstraction)) + abstraction)) (def: .public var (-> Text Var/1) - (|>> :abstraction)) + (|>> abstraction)) (def: .public args (-> (List Var/1) Var/*) (|>> (list#each ..code) (text.interposed " ") ..as_form - :abstraction)) + abstraction)) (def: .public (args& singles rest) (-> (List Var/1) Var/1 Var/*) @@ -162,16 +162,16 @@ (list#each ..code) (text.interposed " ") (text.suffix " "))) - (format "&rest " (:representation rest)) + (format "&rest " (representation rest)) ..as_form - :abstraction)) + abstraction)) (def: form (-> (List (Expression Any)) Expression) (|>> (list#each ..code) (text.interposed " ") ..as_form - :abstraction)) + abstraction)) (def: .public (call/* func) (-> (Expression Any) (-> (List (Expression Any)) (Computation Any))) @@ -190,14 +190,14 @@ (-> (List [Var/1 Lambda]) (Expression Any) (Computation Any)) (..form (list (..var "labels") (..form (list#each (function (_ [def_name [def_args def_body]]) - (..form (list def_name (:transmutation def_args) def_body))) + (..form (list def_name (transmutation def_args) def_body))) definitions)) body))) (def: .public (destructuring_bind [bindings expression] body) (-> [Var/* (Expression Any)] (List (Expression Any)) (Computation Any)) (..form (list& (..var "destructuring-bind") - (:transmutation bindings) expression + (transmutation bindings) expression body))) (template [<call> <input_var>+ <input_type>+ <function>+] @@ -266,7 +266,7 @@ [(`` (template [<lux_name> <host_name>] [(def: .public (<lux_name> args) (-> [(~~ (template.spliced <input_type>+))] (Access Any)) - (:transmutation (<call> args (..var <host_name>))))] + (transmutation (<call> args (..var <host_name>))))] (~~ (template.spliced <function>+))))] @@ -342,7 +342,7 @@ (def: .public (lambda input body) (-> Var/* (Expression Any) Literal) - (..form (list (..var "lambda") (:transmutation input) body))) + (..form (list (..var "lambda") (transmutation input) body))) (template [<lux_name> <host_name>] [(def: .public (<lux_name> bindings body) @@ -364,7 +364,7 @@ (def: .public (defun name inputs body) (-> Var/1 Var/* (Expression Any) (Expression Any)) - (..form (list (..var "defun") name (:transmutation inputs) body))) + (..form (list (..var "defun") name (transmutation inputs) body))) (template [<name> <symbol>] [(def: .public <name> @@ -396,7 +396,7 @@ body (list#each (function (_ [type condition handler]) (..form (list type - (:transmutation (..args (list condition))) + (transmutation (..args (list condition))) handler))) handlers)))) @@ -408,30 +408,30 @@ expression {.#Item single {.#End}} - (:abstraction - (format <prefix> single " " (:representation expression))) + (abstraction + (format <prefix> single " " (representation expression))) _ - (:abstraction + (abstraction (format <prefix> (|> conditions (list#each ..symbol) (list& (..symbol "or")) ..form - :representation) - " " (:representation expression)))))] + representation) + " " (representation expression)))))] [conditional+ "#+"] [conditional- "#-"]) (def: .public label (-> Text Label) - (|>> :abstraction)) + (|>> abstraction)) (def: .public (block name body) (-> Label (List (Expression Any)) (Computation Any)) - (..form (list& (..var "block") (:transmutation name) body))) + (..form (list& (..var "block") (transmutation name) body))) (def: .public (return_from target value) (-> Label (Expression Any) (Computation Any)) - (..form (list (..var "return-from") (:transmutation target) value))) + (..form (list (..var "return-from") (transmutation target) value))) (def: .public (return value) (-> (Expression Any) (Computation Any)) @@ -447,7 +447,7 @@ (def: .public tag (-> Text Tag) - (|>> :abstraction)) + (|>> abstraction)) (def: .public go (-> Tag (Expression Any)) @@ -462,7 +462,7 @@ (def: .public (multiple_value_setq bindings values) (-> Var/* (Expression Any) (Expression Any)) (..form (list (..var "multiple-value-setq") - (:transmutation bindings) + (transmutation bindings) values))) ) diff --git a/stdlib/source/library/lux/target/js.lux b/stdlib/source/library/lux/target/js.lux index e227d6806..6243e3f11 100644 --- a/stdlib/source/library/lux/target/js.lux +++ b/stdlib/source/library/lux/target/js.lux @@ -1,6 +1,6 @@ (.using [library - [lux {"-" Location Code Label or and function if undefined for comment not int try ++ -- the} + [lux {"-" Location Code Label or and function if undefined for comment not int try ++ -- the type_of} [control ["[0]" pipe]] [data @@ -15,7 +15,7 @@ ["i" int] ["f" frac]]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) (def: expression (text.enclosed ["(" ")"])) @@ -38,7 +38,7 @@ (def: .public code (-> (Code Any) Text) - (|>> :representation)) + (|>> representation)) (template [<type> <super>+] [(with_expansions [<brand> (template.symbol [<type> "'"])] @@ -64,7 +64,7 @@ ) (template [<name> <literal>] - [(def: .public <name> Literal (:abstraction <literal>))] + [(def: .public <name> Literal (abstraction <literal>))] [null "null"] [undefined "undefined"] @@ -75,11 +75,11 @@ (|>> (pipe.case #0 "false" #1 "true") - :abstraction)) + abstraction)) (def: .public (number value) (-> Frac Literal) - (:abstraction + (abstraction (cond (f.not_a_number? value) "NaN" @@ -114,7 +114,7 @@ (-> Text Literal) (|>> ..safe (text.enclosed [text.double_quote text.double_quote]) - :abstraction)) + abstraction)) (def: argument_separator ", ") (def: field_separator ": ") @@ -125,19 +125,19 @@ (|>> (list#each ..code) (text.interposed ..argument_separator) ..element - :abstraction)) + abstraction)) (def: .public var (-> Text Var) - (|>> :abstraction)) + (|>> abstraction)) (def: .public (at index array_or_object) (-> Expression Expression Access) - (:abstraction (format (:representation array_or_object) (..element (:representation index))))) + (abstraction (format (representation array_or_object) (..element (representation index))))) (def: .public (the field object) (-> Text Expression Access) - (:abstraction (format (:representation object) "." field))) + (abstraction (format (representation object) "." field))) (def: .public (apply/* function inputs) (-> Expression (List Expression) Computation) @@ -145,8 +145,8 @@ (list#each ..code) (text.interposed ..argument_separator) ..expression - (format (:representation function)) - :abstraction)) + (format (representation function)) + abstraction)) (def: .public (do method inputs object) (-> Text (List Expression) Expression Computation) @@ -155,28 +155,28 @@ (def: .public object (-> (List [Text Expression]) Computation) (|>> (list#each (.function (_ [key val]) - (format (:representation (..string key)) ..field_separator (:representation val)))) + (format (representation (..string key)) ..field_separator (representation val)))) (text.interposed ..argument_separator) (text.enclosed ["{" "}"]) ..expression - :abstraction)) + abstraction)) (def: .public (, pre post) (-> Expression Expression Computation) - (|> (format (:representation pre) ..argument_separator (:representation post)) + (|> (format (representation pre) ..argument_separator (representation post)) ..expression - :abstraction)) + abstraction)) (def: .public (then pre post) (-> Statement Statement Statement) - (:abstraction (format (:representation pre) - \n+ - (:representation post)))) + (abstraction (format (representation pre) + \n+ + (representation post)))) (def: block (-> Statement Text) (let [close (format \n+ "}")] - (|>> :representation + (|>> representation ..nested (text.enclosed ["{" close])))) @@ -185,20 +185,20 @@ (-> Var (List Var) Statement Statement) (|> body ..block - (format "function " (:representation name) + (format "function " (representation name) (|> inputs (list#each ..code) (text.interposed ..argument_separator) ..expression) " ") - :abstraction)) + abstraction)) (def: .public (function name inputs body) (-> Var (List Var) Statement Computation) (|> (..function! name inputs body) - :representation + representation ..expression - :abstraction)) + abstraction)) (def: .public (closure inputs body) (-> (List Var) Statement Computation) @@ -211,14 +211,14 @@ ..expression) " ") ..expression - :abstraction)) + abstraction)) (template [<name> <op>] [(def: .public (<name> param subject) (-> Expression Expression Computation) - (|> (format (:representation subject) " " <op> " " (:representation param)) + (|> (format (representation subject) " " <op> " " (representation param)) ..expression - :abstraction))] + abstraction))] [= "==="] [< "<"] @@ -246,7 +246,7 @@ (template [<prefix> <name>] [(def: .public <name> (-> Expression Computation) - (|>> :representation (text.prefix <prefix>) ..expression :abstraction))] + (|>> representation (text.prefix <prefix>) ..expression abstraction))] ["!" not] ["~" bit_not] @@ -257,131 +257,131 @@ [... A 32-bit integer expression. (def: .public (<name> value) (-> <input> Computation) - (:abstraction (..expression (format (<format> value) "|0"))))] + (abstraction (..expression (format (<format> value) "|0"))))] - [to_i32 Expression :representation] + [to_i32 Expression representation] [i32 Int %.int] ) (def: .public (int value) (-> Int Literal) - (:abstraction (.if (i.< +0 value) - (%.int value) - (%.nat (.nat value))))) + (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)) + (|> (format (representation test) + " ? " (representation then) + " : " (representation else)) ..expression - :abstraction)) + abstraction)) (def: .public type_of (-> Expression Computation) - (|>> :representation + (|>> representation (format "typeof ") ..expression - :abstraction)) + abstraction)) (def: .public (new constructor inputs) (-> Expression (List Expression) Computation) - (|> (format "new " (:representation constructor) + (|> (format "new " (representation constructor) (|> inputs (list#each ..code) (text.interposed ..argument_separator) ..expression)) ..expression - :abstraction)) + abstraction)) (def: .public statement (-> Expression Statement) - (|>> :representation (text.suffix ..statement_suffix) :abstraction)) + (|>> representation (text.suffix ..statement_suffix) abstraction)) (def: .public use_strict Statement - (:abstraction (format text.double_quote "use strict" text.double_quote ..statement_suffix))) + (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))) + (abstraction (format "var " (representation name) ..statement_suffix))) (def: .public (define name value) (-> Var Expression Statement) - (:abstraction (format "var " (:representation name) " = " (:representation value) ..statement_suffix))) + (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))) + (abstraction (format (representation name) " = " (representation value) ..statement_suffix))) (def: .public (throw message) (-> Expression Statement) - (:abstraction (format "throw " (:representation message) ..statement_suffix))) + (abstraction (format "throw " (representation message) ..statement_suffix))) (def: .public (return value) (-> Expression Statement) - (:abstraction (format "return " (:representation value) ..statement_suffix))) + (abstraction (format "return " (representation value) ..statement_suffix))) (def: .public delete (-> Location Expression) - (|>> :representation + (|>> representation (format "delete ") ..expression - :abstraction)) + abstraction)) (def: .public (if test then! else!) (-> Expression Statement Statement Statement) - (:abstraction (format "if(" (:representation test) ") " - (..block then!) - " else " - (..block else!)))) + (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!)))) + (abstraction (format "if(" (representation test) ") " + (..block then!)))) (def: .public (while test body) (-> Expression Statement Loop) - (:abstraction (format "while(" (:representation test) ") " - (..block body)))) + (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))) + (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)))) + (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)))) + (abstraction (format "for(" (representation (..define var init)) + " " (representation condition) + ..statement_suffix " " (representation update) + ")" + (..block iteration)))) (def: .public label (-> Text Label) - (|>> :abstraction)) + (|>> abstraction)) (def: .public (with_label label loop) (-> Label Loop Statement) - (:abstraction (format (:representation label) ": " (:representation loop)))) + (abstraction (format (representation label) ": " (representation loop)))) (template [<keyword> <0> <1>] [(def: .public <0> Statement - (:abstraction (format <keyword> ..statement_suffix))) + (abstraction (format <keyword> ..statement_suffix))) (def: .public (<1> label) (-> Label Statement) - (:abstraction (format <keyword> " " (:representation label) ..statement_suffix)))] + (abstraction (format <keyword> " " (representation label) ..statement_suffix)))] ["break" break break_at] ["continue" continue continue_at] @@ -390,9 +390,9 @@ (template [<name> <js>] [(def: .public <name> (-> Location Expression) - (|>> :representation + (|>> representation (text.suffix <js>) - :abstraction))] + abstraction))] [++ "++"] [-- "--"] @@ -400,28 +400,28 @@ (def: .public (comment commentary on) (All (_ kind) (-> Text (Code kind) (Code kind))) - (:abstraction (format "/* " commentary " */" " " (:representation on)))) + (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 \n+)) - (..nested (:representation then))))) - (text.interposed \n+)) - \n+ - (case default - {.#Some default} - (format "default:" - (..nested (:representation default))) - - {.#None} - "")) - :abstraction - ..block)))) + (abstraction (format "switch (" (representation input) ") " + (|> (format (|> cases + (list#each (.function (_ [when then]) + (format (|> when + (list#each (|>> representation (text.enclosed ["case " ":"]))) + (text.interposed \n+)) + (..nested (representation then))))) + (text.interposed \n+)) + \n+ + (case default + {.#Some default} + (format "default:" + (..nested (representation default))) + + {.#None} + "")) + abstraction + ..block)))) ) (template [<apply> <arg>+ <type>+ <function>+] diff --git a/stdlib/source/library/lux/target/jvm/bytecode.lux b/stdlib/source/library/lux/target/jvm/bytecode.lux index 895d84f7a..a58bce01c 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode.lux @@ -88,7 +88,7 @@ <then> failure - (:expected failure))]) + (as_expected failure))]) (template: (try|in <it>) [{try.#Success <it>}]) @@ -213,7 +213,7 @@ ... {try.#Failure error} failure - (:expected failure))))) + (as_expected failure))))) (implementation: .public monad (Monad Bytecode) @@ -234,11 +234,11 @@ ... {try.#Failure error} failure - (:expected failure)) + (as_expected failure)) ... {try.#Failure error} failure - (:expected failure))))) + (as_expected failure))))) (def: .public (when_continuous it) (-> (Bytecode Any) (Bytecode Any)) @@ -611,17 +611,17 @@ (-> java/lang/Float Int) (|>> java/lang/Float::floatToRawIntBits ffi.int_to_long - (:as Int))) + (as Int))) (def: negative_zero_float_bits - (|> -0.0 (:as java/lang/Double) ffi.double_to_float ..float_bits)) + (|> -0.0 (as java/lang/Double) ffi.double_to_float ..float_bits)) (def: .public (float value) (-> java/lang/Float (Bytecode Any)) (if (i.= ..negative_zero_float_bits (..float_bits value)) (..arbitrary_float value) - (case (|> value ffi.float_to_double (:as Frac)) + (case (|> value ffi.float_to_double (as Frac)) (^.template [<special> <instruction>] [<special> (..bytecode $0 $1 @_ <instruction> [])]) ([+0.0 _.fconst_0] @@ -651,23 +651,23 @@ (def: (arbitrary_double value) (-> java/lang/Double (Bytecode Any)) (do ..monad - [index (..lifted (//constant/pool.double (//constant.double (:as Frac value))))] + [index (..lifted (//constant/pool.double (//constant.double (as Frac value))))] (..bytecode $0 $2 @_ _.ldc2_w/double [index]))) (def: double_bits (-> java/lang/Double Int) (|>> java/lang/Double::doubleToRawLongBits - (:as Int))) + (as Int))) (def: negative_zero_double_bits - (..double_bits (:as java/lang/Double -0.0))) + (..double_bits (as java/lang/Double -0.0))) (def: .public (double value) (-> java/lang/Double (Bytecode Any)) (if (i.= ..negative_zero_double_bits (..double_bits value)) (..arbitrary_double value) - (case (:as Frac value) + (case (as Frac value) (^.template [<special> <instruction>] [<special> (..bytecode $0 $2 @_ <instruction> [])]) ([+0.0 _.dconst_0] @@ -950,9 +950,9 @@ (|> (list#mix (..acknowledge_label actual) tracker (list& default at_minimum afterwards)) (has #program_counter program_counter'))] [(function (_ resolver) - (let [get (: (-> Label (Maybe [Stack (Maybe Address)])) - (function (_ label) - (dictionary.value label resolver)))] + (let [get (is (-> Label (Maybe [Stack (Maybe Address)])) + (function (_ label) + (dictionary.value label resolver)))] (case (do [! maybe.monad] [@default (|> default get (monad.then ! product.right)) @at_minimum (|> at_minimum get (monad.then ! product.right))] @@ -992,9 +992,9 @@ (|> (list#mix (..acknowledge_label actual) tracker (list& default (list#each product.right cases))) (has #program_counter program_counter'))] [(function (_ resolver) - (let [get (: (-> Label (Maybe [Stack (Maybe Address)])) - (function (_ label) - (dictionary.value label resolver)))] + (let [get (is (-> Label (Maybe [Stack (Maybe Address)])) + (function (_ label) + (dictionary.value label resolver)))] (case (do [! maybe.monad] [@default (|> default get (monad.then ! product.right))] (|> cases @@ -1045,10 +1045,10 @@ (def: .public (multianewarray class dimensions) (-> (Type Object) U1 (Bytecode Any)) (do ..monad - [_ (: (Bytecode Any) - (case (|> dimensions //unsigned.value) - 0 (..except ..multiarray_cannot_be_zero_dimensional [class]) - _ (in []))) + [_ (is (Bytecode Any) + (case (|> dimensions //unsigned.value) + 0 (..except ..multiarray_cannot_be_zero_dimensional [class]) + _ (in []))) index (..lifted (//constant/pool.class (//name.internal (..reflection class))))] (..bytecode (//unsigned.lifted/2 dimensions) $1 @_ _.multianewarray [index dimensions]))) @@ -1170,4 +1170,4 @@ ... {try.#Failure error} failure - (:expected failure)))) + (as_expected failure)))) diff --git a/stdlib/source/library/lux/target/jvm/bytecode/address.lux b/stdlib/source/library/lux/target/jvm/bytecode/address.lux index f91c4025f..f0df22eb4 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode/address.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode/address.lux @@ -1,48 +1,48 @@ (.using - [library - [lux "*" - [abstract - [equivalence {"+" Equivalence}] - [monad {"+" do}]] - [control - ["[0]" try {"+" Try}]] - [data - [format - [binary {"+" Writer}]] - [text - ["%" format {"+" Format}]]] - [math - [number - ["n" nat]]] - [type - abstract]]] - ["[0]" // "_" - [jump {"+" Big_Jump}] - ["/[1]" // "_" - [encoding - ["[1][0]" unsigned {"+" U2}] - ["[1][0]" signed {"+" S4}]]]]) + [library + [lux "*" + [abstract + [equivalence {"+" Equivalence}] + [monad {"+" do}]] + [control + ["[0]" try {"+" Try}]] + [data + [format + [binary {"+" Writer}]] + [text + ["%" format {"+" Format}]]] + [math + [number + ["n" nat]]] + [type + [abstract {"-" pattern}]]]] + ["[0]" // "_" + [jump {"+" Big_Jump}] + ["/[1]" // "_" + [encoding + ["[1][0]" unsigned {"+" U2}] + ["[1][0]" signed {"+" S4}]]]]) (abstract: .public Address U2 (def: .public value (-> Address U2) - (|>> :representation)) + (|>> representation)) (def: .public start Address - (|> 0 ///unsigned.u2 try.trusted :abstraction)) + (|> 0 ///unsigned.u2 try.trusted abstraction)) (def: .public (move distance) (-> U2 (-> Address (Try Address))) - (|>> :representation + (|>> representation (///unsigned.+/2 distance) - (# try.functor each (|>> :abstraction)))) + (# try.functor each (|>> abstraction)))) (def: with_sign (-> Address (Try S4)) - (|>> :representation ///unsigned.value .int ///signed.s4)) + (|>> representation ///unsigned.value .int ///signed.s4)) (def: .public (jump from to) (-> Address Address (Try Big_Jump)) @@ -53,22 +53,22 @@ (def: .public (after? reference subject) (-> Address Address Bit) - (n.> (|> reference :representation ///unsigned.value) - (|> subject :representation ///unsigned.value))) + (n.> (|> reference representation ///unsigned.value) + (|> subject representation ///unsigned.value))) (implementation: .public equivalence (Equivalence Address) (def: (= reference subject) (# ///unsigned.equivalence = - (:representation reference) - (:representation subject)))) + (representation reference) + (representation subject)))) (def: .public writer (Writer Address) - (|>> :representation ///unsigned.writer/2)) + (|>> representation ///unsigned.writer/2)) (def: .public format (Format Address) - (|>> :representation ///unsigned.value %.nat)) + (|>> representation ///unsigned.value %.nat)) ) diff --git a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux index 4f42ccffc..b7952504e 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/registry.lux @@ -14,7 +14,7 @@ [number ["n" nat]]] [type - abstract]]] + [abstract {"-" pattern}]]]] ["[0]" ///// "_" [encoding ["[1][0]" unsigned {"+" U1 U2}]] @@ -33,7 +33,7 @@ (def: .public registry (-> U2 Registry) - (|>> :abstraction)) + (|>> abstraction)) (def: (minimal type) (-> (Type Method) Nat) @@ -61,18 +61,18 @@ (def: .public equivalence (Equivalence Registry) (# equivalence.functor each - (|>> :representation) + (|>> representation) /////unsigned.equivalence)) (def: .public writer (Writer Registry) - (|>> :representation /////unsigned.writer/2)) + (|>> representation /////unsigned.writer/2)) (def: .public (has needed) (-> Registry Registry Registry) - (|>> :representation - (/////unsigned.max/2 (:representation needed)) - :abstraction)) + (|>> representation + (/////unsigned.max/2 (representation needed)) + abstraction)) (template [<name> <extra>] [(def: .public <name> @@ -81,7 +81,7 @@ (|>> /////unsigned.lifted/2 (/////unsigned.+/2 extra) try.trusted - :abstraction)))] + abstraction)))] [for ..normal] [for_wide ..wide] diff --git a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/stack.lux b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/stack.lux index e67bb157b..4b7b29804 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/stack.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode/environment/limit/stack.lux @@ -1,21 +1,21 @@ (.using - [library - [lux "*" - [abstract - ["[0]" equivalence {"+" Equivalence}]] - [control - ["[0]" maybe] - ["[0]" try {"+" Try}]] - [data - [text - ["%" format {"+" Format}]] - [format - [binary {"+" Writer}]]] - [type - abstract]]] - ["[0]" ///// "_" - [encoding - ["[1][0]" unsigned {"+" U2}]]]) + [library + [lux "*" + [abstract + ["[0]" equivalence {"+" Equivalence}]] + [control + ["[0]" maybe] + ["[0]" try {"+" Try}]] + [data + [text + ["%" format {"+" Format}]] + [format + [binary {"+" Writer}]]] + [type + [abstract {"-" pattern}]]]] + ["[0]" ///// "_" + [encoding + ["[1][0]" unsigned {"+" U2}]]]) (abstract: .public Stack U2 @@ -23,7 +23,7 @@ (template [<frames> <name>] [(def: .public <name> Stack - (|> <frames> /////unsigned.u2 maybe.trusted :abstraction))] + (|> <frames> /////unsigned.u2 maybe.trusted abstraction))] [0 empty] [1 catch] @@ -32,21 +32,21 @@ (def: .public equivalence (Equivalence Stack) (# equivalence.functor each - (|>> :representation) + (|>> representation) /////unsigned.equivalence)) (def: .public writer (Writer Stack) - (|>> :representation /////unsigned.writer/2)) + (|>> representation /////unsigned.writer/2)) (def: stack (-> U2 Stack) - (|>> :abstraction)) + (|>> abstraction)) (template [<op> <name>] [(def: .public (<name> amount) (-> U2 (-> Stack (Try Stack))) - (|>> :representation + (|>> representation (<op> amount) (# try.functor each ..stack)))] @@ -56,13 +56,13 @@ (def: .public (max left right) (-> Stack Stack Stack) - (:abstraction - (/////unsigned.max/2 (:representation left) - (:representation right)))) + (abstraction + (/////unsigned.max/2 (representation left) + (representation right)))) (def: .public format (Format Stack) - (|>> :representation /////unsigned.value %.nat)) + (|>> representation /////unsigned.value %.nat)) ) (def: .public length diff --git a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux index 4f371461a..237901cf1 100644 --- a/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux +++ b/stdlib/source/library/lux/target/jvm/bytecode/instruction.lux @@ -23,7 +23,7 @@ [number {"+" hex} ["n" nat]]] [type - abstract]]] + [abstract {"-" pattern}]]]] ["[0]" // "_" ["[1][0]" address {"+" Address}] ["[1][0]" jump {"+" Jump Big_Jump}] @@ -227,11 +227,11 @@ (def: code (-> Primitive_Array_Type U1) - (|>> :representation)) + (|>> representation)) (template [<code> <name>] [(def: .public <name> - (|> <code> ///unsigned.u1 try.trusted :abstraction))] + (|> <code> ///unsigned.u1 try.trusted abstraction))] [04 t_boolean] [05 t_char] @@ -576,18 +576,18 @@ (def: .public tableswitch [(-> Nat Estimator) (-> S4 Big_Jump [Big_Jump (List Big_Jump)] Instruction)] - (let [estimator (: (-> Nat Estimator) - (function (_ amount_of_afterwards offset) - (|> ($_ n.+ - (///unsigned.value ..opcode_size) - (switch_padding (///unsigned.value (//address.value offset))) - (///unsigned.value ..big_jump_size) - (///unsigned.value ..integer_size) - (///unsigned.value ..integer_size) - (n.* (///unsigned.value ..big_jump_size) - (++ amount_of_afterwards))) - ///unsigned.u2 - try.trusted)))] + (let [estimator (is (-> Nat Estimator) + (function (_ amount_of_afterwards offset) + (|> ($_ n.+ + (///unsigned.value ..opcode_size) + (switch_padding (///unsigned.value (//address.value offset))) + (///unsigned.value ..big_jump_size) + (///unsigned.value ..integer_size) + (///unsigned.value ..integer_size) + (n.* (///unsigned.value ..big_jump_size) + (++ amount_of_afterwards))) + ///unsigned.u2 + try.trusted)))] [estimator (function (_ minimum default [at_minimum afterwards]) (let [amount_of_afterwards (list.size afterwards) @@ -599,40 +599,40 @@ [size (///unsigned.u2 size)] (# ! each (|>> estimator ///unsigned.value) (//address.move size //address.start)))) - tableswitch_mutation (: Mutation - (function (_ [offset binary]) - [(n.+ tableswitch_size offset) - (try.trusted - (do [! try.monad] - [amount_of_afterwards (|> amount_of_afterwards .int ///signed.s4) - maximum (///signed.+/4 minimum amount_of_afterwards)] - (in (let [_ (binary.with/1! offset (hex "AA") binary) - offset (n.+ (///unsigned.value ..opcode_size) offset) - _ (case padding - 3 (|> binary - (binary.with/1! offset 0) - (binary.with/2! (++ offset) 0)) - 2 (binary.with/2! offset 0 binary) - 1 (binary.with/1! offset 0 binary) - _ binary) - offset (n.+ padding offset) - _ (binary.with/4! offset (///signed.value default) binary) - offset (n.+ (///unsigned.value ..big_jump_size) offset) - _ (binary.with/4! offset (///signed.value minimum) binary) - offset (n.+ (///unsigned.value ..integer_size) offset) - _ (binary.with/4! offset (///signed.value maximum) binary)] - (loop [offset (n.+ (///unsigned.value ..integer_size) offset) - afterwards (: (List Big_Jump) - {.#Item at_minimum afterwards})] - (case afterwards - {.#End} - binary - - {.#Item head tail} - (exec - (binary.with/4! offset (///signed.value head) binary) - (again (n.+ (///unsigned.value ..big_jump_size) offset) - tail))))))))]))] + tableswitch_mutation (is Mutation + (function (_ [offset binary]) + [(n.+ tableswitch_size offset) + (try.trusted + (do [! try.monad] + [amount_of_afterwards (|> amount_of_afterwards .int ///signed.s4) + maximum (///signed.+/4 minimum amount_of_afterwards)] + (in (let [_ (binary.with/1! offset (hex "AA") binary) + offset (n.+ (///unsigned.value ..opcode_size) offset) + _ (case padding + 3 (|> binary + (binary.with/1! offset 0) + (binary.with/2! (++ offset) 0)) + 2 (binary.with/2! offset 0 binary) + 1 (binary.with/1! offset 0 binary) + _ binary) + offset (n.+ padding offset) + _ (binary.with/4! offset (///signed.value default) binary) + offset (n.+ (///unsigned.value ..big_jump_size) offset) + _ (binary.with/4! offset (///signed.value minimum) binary) + offset (n.+ (///unsigned.value ..integer_size) offset) + _ (binary.with/4! offset (///signed.value maximum) binary)] + (loop [offset (n.+ (///unsigned.value ..integer_size) offset) + afterwards (is (List Big_Jump) + {.#Item at_minimum afterwards})] + (case afterwards + {.#End} + binary + + {.#Item head tail} + (exec + (binary.with/4! offset (///signed.value head) binary) + (again (n.+ (///unsigned.value ..big_jump_size) offset) + tail))))))))]))] [(n.+ tableswitch_size size) (|>> mutation tableswitch_mutation)]))))])) @@ -642,16 +642,16 @@ (-> Big_Jump (List [S4 Big_Jump]) Instruction)] (let [case_size (n.+ (///unsigned.value ..integer_size) (///unsigned.value ..big_jump_size)) - estimator (: (-> Nat Estimator) - (function (_ amount_of_cases offset) - (|> ($_ n.+ - (///unsigned.value ..opcode_size) - (switch_padding (///unsigned.value (//address.value offset))) - (///unsigned.value ..big_jump_size) - (///unsigned.value ..integer_size) - (n.* amount_of_cases case_size)) - ///unsigned.u2 - try.trusted)))] + estimator (is (-> Nat Estimator) + (function (_ amount_of_cases offset) + (|> ($_ n.+ + (///unsigned.value ..opcode_size) + (switch_padding (///unsigned.value (//address.value offset))) + (///unsigned.value ..big_jump_size) + (///unsigned.value ..integer_size) + (n.* amount_of_cases case_size)) + ///unsigned.u2 + try.trusted)))] [estimator (function (_ default cases) (let [amount_of_cases (list.size cases) @@ -663,34 +663,34 @@ [size (///unsigned.u2 size)] (# ! each (|>> estimator ///unsigned.value) (//address.move size //address.start)))) - lookupswitch_mutation (: Mutation - (function (_ [offset binary]) - [(n.+ lookupswitch_size offset) - (let [_ (binary.with/1! offset (hex "AB") binary) - offset (n.+ (///unsigned.value ..opcode_size) offset) - _ (case padding - 3 (|> binary - (binary.with/1! offset 0) - (binary.with/2! (++ offset) 0)) - 2 (binary.with/2! offset 0 binary) - 1 (binary.with/1! offset 0 binary) - _ binary) - offset (n.+ padding offset) - _ (binary.with/4! offset (///signed.value default) binary) - offset (n.+ (///unsigned.value ..big_jump_size) offset) - _ (binary.with/4! offset amount_of_cases binary)] - (loop [offset (n.+ (///unsigned.value ..integer_size) offset) - cases cases] - (case cases - {.#End} - binary - - {.#Item [value jump] tail} - (exec - (binary.with/4! offset (///signed.value value) binary) - (binary.with/4! (n.+ (///unsigned.value ..integer_size) offset) (///signed.value jump) binary) - (again (n.+ case_size offset) - tail)))))]))] + lookupswitch_mutation (is Mutation + (function (_ [offset binary]) + [(n.+ lookupswitch_size offset) + (let [_ (binary.with/1! offset (hex "AB") binary) + offset (n.+ (///unsigned.value ..opcode_size) offset) + _ (case padding + 3 (|> binary + (binary.with/1! offset 0) + (binary.with/2! (++ offset) 0)) + 2 (binary.with/2! offset 0 binary) + 1 (binary.with/1! offset 0 binary) + _ binary) + offset (n.+ padding offset) + _ (binary.with/4! offset (///signed.value default) binary) + offset (n.+ (///unsigned.value ..big_jump_size) offset) + _ (binary.with/4! offset amount_of_cases binary)] + (loop [offset (n.+ (///unsigned.value ..integer_size) offset) + cases cases] + (case cases + {.#End} + binary + + {.#Item [value jump] tail} + (exec + (binary.with/4! offset (///signed.value value) binary) + (binary.with/4! (n.+ (///unsigned.value ..integer_size) offset) (///signed.value jump) binary) + (again (n.+ case_size offset) + tail)))))]))] [(n.+ lookupswitch_size size) (|>> mutation lookupswitch_mutation)]))))])) diff --git a/stdlib/source/library/lux/target/jvm/class.lux b/stdlib/source/library/lux/target/jvm/class.lux index 73966259f..4d2cf203c 100644 --- a/stdlib/source/library/lux/target/jvm/class.lux +++ b/stdlib/source/library/lux/target/jvm/class.lux @@ -77,13 +77,13 @@ (do [! //pool.monad] [@this (//pool.class this) @super (//pool.class super) - @interfaces (: (Resource (Sequence (Index //constant.Class))) - (monad.mix ! (function (_ interface @interfaces) - (do ! - [@interface (//pool.class interface)] - (in (sequence.suffix @interface @interfaces)))) - sequence.empty - interfaces))] + @interfaces (is (Resource (Sequence (Index //constant.Class))) + (monad.mix ! (function (_ interface @interfaces) + (do ! + [@interface (//pool.class interface)] + (in (sequence.suffix @interface @interfaces)))) + sequence.empty + interfaces))] (in [@this @super @interfaces]))) (def: .public (class version modifier diff --git a/stdlib/source/library/lux/target/jvm/constant.lux b/stdlib/source/library/lux/target/jvm/constant.lux index 71aab1ed3..1afa70f79 100644 --- a/stdlib/source/library/lux/target/jvm/constant.lux +++ b/stdlib/source/library/lux/target/jvm/constant.lux @@ -22,7 +22,7 @@ ["[0]" int] ["[0]" frac]]] [type - abstract]]] + [abstract {"-" pattern}]]]] ["[0]" / "_" ["[1][0]" tag] ["/[1]" // "_" @@ -45,11 +45,11 @@ (def: .public index (-> Class (Index UTF8)) - (|>> :representation)) + (|>> representation)) (def: .public class (-> (Index UTF8) Class) - (|>> :abstraction)) + (|>> abstraction)) (def: .public class_equivalence (Equivalence Class) @@ -59,7 +59,7 @@ (def: class_writer (Writer Class) - (|>> :representation //index.writer)) + (|>> representation //index.writer)) ) (import: java/lang/Float @@ -87,14 +87,14 @@ (def: .public value (All (_ kind) (-> (Value kind) kind)) - (|>> :representation)) + (|>> representation)) (def: .public (value_equivalence Equivalence<kind>) (All (_ kind) (-> (Equivalence kind) (Equivalence (Value kind)))) (# equivalence.functor each - (|>> :representation) + (|>> representation) Equivalence<kind>)) (template [<constructor> <type> <marker>] @@ -103,7 +103,7 @@ (def: .public <constructor> (-> <marker> <type>) - (|>> :abstraction))] + (|>> abstraction))] [integer Integer I32] [float Float java/lang/Float] @@ -115,7 +115,7 @@ (template [<writer_name> <type> <write> <writer>] [(def: <writer_name> (Writer <type>) - (`` (|>> :representation + (`` (|>> representation (~~ (template.spliced <write>)) (~~ (template.spliced <writer>)))))] diff --git a/stdlib/source/library/lux/target/jvm/constant/pool.lux b/stdlib/source/library/lux/target/jvm/constant/pool.lux index 666531963..e2fcfd655 100644 --- a/stdlib/source/library/lux/target/jvm/constant/pool.lux +++ b/stdlib/source/library/lux/target/jvm/constant/pool.lux @@ -55,7 +55,7 @@ ... {try.#Failure error} failure - (:expected failure))))) + (as_expected failure))))) (implementation: .public monad (Monad Resource) @@ -74,7 +74,7 @@ ... {try.#Failure error} failure - (:expected failure))))) + (as_expected failure))))) (template: (try|each <binding> <value> <body>) [(case <value> @@ -83,7 +83,7 @@ ... {try.#Failure error} failure - (:expected failure))]) + (as_expected failure))]) (template: (try|in <it>) [{try.#Success <it>}]) @@ -108,11 +108,11 @@ {try.#Failure _} (<| (let [new {<tag> <value>'}]) (try|each @new (//unsigned.u2 (//.size new))) - (try|each next (: (Try Index) - (|> current - //index.value - (//unsigned.+/2 @new) - (# try.monad each //index.index)))) + (try|each next (is (Try Index) + (|> current + //index.value + (//unsigned.+/2 @new) + (# try.monad each //index.index)))) (try|in [[next (sequence.suffix [current new] pool)] current]))))))]) @@ -128,7 +128,7 @@ ... {try.#Failure error} failure - (:expected failure))]) + (as_expected failure))]) (type: (Adder of) (-> of (Resource (Index of)))) diff --git a/stdlib/source/library/lux/target/jvm/constant/tag.lux b/stdlib/source/library/lux/target/jvm/constant/tag.lux index 8d8d162aa..36acb163f 100644 --- a/stdlib/source/library/lux/target/jvm/constant/tag.lux +++ b/stdlib/source/library/lux/target/jvm/constant/tag.lux @@ -1,18 +1,18 @@ (.using - [library - [lux "*" - [abstract - [equivalence {"+" Equivalence}]] - [control - ["[0]" try]] - [data - [format - [binary {"+" Writer}]]] - [type - abstract]]] - ["[0]" /// "_" - [encoding - ["[1][0]" unsigned {"+" U1} ("u1//[0]" equivalence)]]]) + [library + [lux "*" + [abstract + [equivalence {"+" Equivalence}]] + [control + ["[0]" try]] + [data + [format + [binary {"+" Writer}]]] + [type + [abstract {"-" pattern}]]]] + ["[0]" /// "_" + [encoding + ["[1][0]" unsigned {"+" U1} ("u1//[0]" equivalence)]]]) (abstract: .public Tag U1 @@ -20,13 +20,13 @@ (implementation: .public equivalence (Equivalence Tag) (def: (= reference sample) - (u1//= (:representation reference) - (:representation sample)))) + (u1//= (representation reference) + (representation sample)))) (template [<code> <name>] [(def: .public <name> Tag - (|> <code> ///unsigned.u1 try.trusted :abstraction))] + (|> <code> ///unsigned.u1 try.trusted abstraction))] [01 utf8] [03 integer] @@ -46,5 +46,5 @@ (def: .public writer (Writer Tag) - (|>> :representation ///unsigned.writer/1)) + (|>> representation ///unsigned.writer/1)) ) diff --git a/stdlib/source/library/lux/target/jvm/encoding/name.lux b/stdlib/source/library/lux/target/jvm/encoding/name.lux index c935d07b0..247300884 100644 --- a/stdlib/source/library/lux/target/jvm/encoding/name.lux +++ b/stdlib/source/library/lux/target/jvm/encoding/name.lux @@ -1,11 +1,11 @@ (.using - [library - [lux "*" - [data - ["[0]" text - ["%" format {"+" format}]]] - [type - abstract]]]) + [library + [lux "*" + [data + ["[0]" text + ["%" format {"+" format}]]] + [type + [abstract {"-" pattern}]]]]) (def: .public internal_separator "/") (def: .public external_separator ".") @@ -20,15 +20,15 @@ (-> External Internal) (|>> (text.replaced ..external_separator ..internal_separator) - :abstraction)) + abstraction)) (def: .public read (-> Internal Text) - (|>> :representation)) + (|>> representation)) (def: .public external (-> Internal External) - (|>> :representation + (|>> representation (text.replaced ..internal_separator ..external_separator)))) diff --git a/stdlib/source/library/lux/target/jvm/encoding/signed.lux b/stdlib/source/library/lux/target/jvm/encoding/signed.lux index dba35fc11..981d8c3f7 100644 --- a/stdlib/source/library/lux/target/jvm/encoding/signed.lux +++ b/stdlib/source/library/lux/target/jvm/encoding/signed.lux @@ -20,26 +20,26 @@ ["n" nat] ["i" int]]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) (abstract: .public (Signed brand) Int (def: .public value (-> (Signed Any) Int) - (|>> :representation)) + (|>> representation)) (implementation: .public equivalence (All (_ brand) (Equivalence (Signed brand))) (def: (= reference sample) - (i.= (:representation reference) (:representation sample)))) + (i.= (representation reference) (representation sample)))) (implementation: .public order (All (_ brand) (Order (Signed brand))) (def: &equivalence ..equivalence) (def: (< reference sample) - (i.< (:representation reference) (:representation sample)))) + (i.< (representation reference) (representation sample)))) (exception: .public (value_exceeds_the_scope [value Int scope Nat]) @@ -56,31 +56,31 @@ (def: .public <maximum> <name> - (|> <bytes> (n.* i64.bits_per_byte) -- i64.mask :abstraction)) + (|> <bytes> (n.* i64.bits_per_byte) -- i64.mask abstraction)) (def: .public <minimum> <name> - (let [it (:representation <maximum>)] - (:abstraction (-- (i.- it +0))))) + (let [it (representation <maximum>)] + (abstraction (-- (i.- it +0))))) (def: .public <constructor> (-> Int (Try <name>)) - (let [positive (:representation <maximum>) + (let [positive (representation <maximum>) negative (i64.not positive)] (function (_ value) (if (i.= (if (i.< +0 value) (i64.or negative value) (i64.and positive value)) value) - {try.#Success (:abstraction value)} + {try.#Success (abstraction value)} (exception.except ..value_exceeds_the_scope [value <size>]))))) (template [<abstract_operation> <concrete_operation>] [(def: .public (<abstract_operation> parameter subject) (-> <name> <name> (Try <name>)) (<constructor> - (<concrete_operation> (:representation parameter) - (:representation subject))))] + (<concrete_operation> (representation parameter) + (representation subject))))] [<+> i.+] [<-> i.-] @@ -94,7 +94,7 @@ (template [<name> <from> <to>] [(def: .public <name> (-> <from> <to>) - (|>> :transmutation))] + (|>> transmutation))] [lifted/2 S1 S2] [lifted/4 S2 S4] @@ -103,7 +103,7 @@ (template [<writer_name> <type> <writer>] [(def: .public <writer_name> (Writer <type>) - (|>> :representation <writer>))] + (|>> representation <writer>))] [writer/1 S1 format.bits/8] [writer/2 S2 format.bits/16] diff --git a/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux b/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux index 795f30716..d733b0480 100644 --- a/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux +++ b/stdlib/source/library/lux/target/jvm/encoding/unsigned.lux @@ -19,28 +19,28 @@ ["n" nat] ["[0]" i64]]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) (abstract: .public (Unsigned brand) Nat (def: .public value (-> (Unsigned Any) Nat) - (|>> :representation)) + (|>> representation)) (implementation: .public equivalence (All (_ brand) (Equivalence (Unsigned brand))) (def: (= reference sample) - (n.= (:representation reference) - (:representation sample)))) + (n.= (representation reference) + (representation sample)))) (implementation: .public order (All (_ brand) (Order (Unsigned brand))) (def: &equivalence ..equivalence) (def: (< reference sample) - (n.< (:representation reference) - (:representation sample)))) + (n.< (representation reference) + (representation sample)))) (exception: .public (value_exceeds_the_maximum [type Symbol value Nat @@ -48,7 +48,7 @@ (exception.report "Type" (%.symbol type) "Value" (%.nat value) - "Maximum" (%.nat (:representation maximum)))) + "Maximum" (%.nat (representation maximum)))) (exception: .public [brand] (subtraction_cannot_yield_negative_value [type Symbol @@ -56,8 +56,8 @@ subject (Unsigned brand)]) (exception.report "Type" (%.symbol type) - "Parameter" (%.nat (:representation parameter)) - "Subject" (%.nat (:representation subject)))) + "Parameter" (%.nat (representation parameter)) + "Subject" (%.nat (representation subject)))) (template [<bytes> <name> <size> <constructor> <maximum> <+> <-> <max>] [(with_expansions [<raw> (template.symbol [<name> "'"])] @@ -68,32 +68,32 @@ (def: .public <maximum> <name> - (|> <bytes> (n.* i64.bits_per_byte) i64.mask :abstraction)) + (|> <bytes> (n.* i64.bits_per_byte) i64.mask abstraction)) (def: .public (<constructor> value) (-> Nat (Try <name>)) - (if (n.> (:representation <maximum>) value) + (if (n.> (representation <maximum>) value) (exception.except ..value_exceeds_the_maximum [(symbol <name>) value <maximum>]) - {try.#Success (:abstraction value)})) + {try.#Success (abstraction value)})) (def: .public (<+> parameter subject) (-> <name> <name> (Try <name>)) (<constructor> - (n.+ (:representation parameter) - (:representation subject)))) + (n.+ (representation parameter) + (representation subject)))) (def: .public (<-> parameter subject) (-> <name> <name> (Try <name>)) - (let [parameter' (:representation parameter) - subject' (:representation subject)] + (let [parameter' (representation parameter) + subject' (representation subject)] (if (n.> subject' parameter') (exception.except ..subtraction_cannot_yield_negative_value [(symbol <name>) parameter subject]) - {try.#Success (:abstraction (n.- parameter' subject'))}))) + {try.#Success (abstraction (n.- parameter' subject'))}))) (def: .public (<max> left right) (-> <name> <name> <name>) - (:abstraction (n.max (:representation left) - (:representation right))))] + (abstraction (n.max (representation left) + (representation right))))] [1 U1 bytes/1 u1 maximum/1 +/1 -/1 max/1] [2 U2 bytes/2 u2 maximum/2 +/2 -/2 max/2] @@ -103,7 +103,7 @@ (template [<name> <from> <to>] [(def: .public <name> (-> <from> <to>) - (|>> :transmutation))] + (|>> transmutation))] [lifted/2 U1 U2] [lifted/4 U2 U4] @@ -112,7 +112,7 @@ (template [<writer_name> <type> <writer>] [(def: .public <writer_name> (Writer <type>) - (|>> :representation <writer>))] + (|>> representation <writer>))] [writer/1 U1 format.bits/8] [writer/2 U2 format.bits/16] diff --git a/stdlib/source/library/lux/target/jvm/index.lux b/stdlib/source/library/lux/target/jvm/index.lux index 8b339bc89..b6a0eb318 100644 --- a/stdlib/source/library/lux/target/jvm/index.lux +++ b/stdlib/source/library/lux/target/jvm/index.lux @@ -1,16 +1,16 @@ (.using - [library - [lux "*" - [abstract - ["[0]" equivalence {"+" Equivalence}]] - [data - [format - [binary {"+" Writer}]]] - [type - abstract]]] - ["[0]" // "_" - [encoding - ["[1][0]" unsigned {"+" U2}]]]) + [library + [lux "*" + [abstract + ["[0]" equivalence {"+" Equivalence}]] + [data + [format + [binary {"+" Writer}]]] + [type + [abstract {"-" pattern}]]]] + ["[0]" // "_" + [encoding + ["[1][0]" unsigned {"+" U2}]]]) (def: .public length //unsigned.bytes/2) @@ -20,11 +20,11 @@ (def: .public index (All (_ kind) (-> U2 (Index kind))) - (|>> :abstraction)) + (|>> abstraction)) (def: .public value (-> (Index Any) U2) - (|>> :representation)) + (|>> representation)) (def: .public equivalence (All (_ kind) (Equivalence (Index kind))) @@ -34,5 +34,5 @@ (def: .public writer (All (_ kind) (Writer (Index kind))) - (|>> :representation //unsigned.writer/2)) + (|>> representation //unsigned.writer/2)) ) diff --git a/stdlib/source/library/lux/target/jvm/loader.lux b/stdlib/source/library/lux/target/jvm/loader.lux index 71d6dc712..bff3cb325 100644 --- a/stdlib/source/library/lux/target/jvm/loader.lux +++ b/stdlib/source/library/lux/target/jvm/loader.lux @@ -68,13 +68,13 @@ (def: java/lang/ClassLoader::defineClass java/lang/reflect/Method (let [signature (|> (ffi.array <elemT> 4) - (ffi.write! 0 (:as <elemT> - (ffi.class_for java/lang/String))) + (ffi.write! 0 (as <elemT> + (ffi.class_for java/lang/String))) (ffi.write! 1 (java/lang/Object::getClass (ffi.array byte 0))) - (ffi.write! 2 (:as <elemT> - (java/lang/Integer::TYPE))) - (ffi.write! 3 (:as <elemT> - (java/lang/Integer::TYPE))))] + (ffi.write! 2 (as <elemT> + (java/lang/Integer::TYPE))) + (ffi.write! 3 (as <elemT> + (java/lang/Integer::TYPE))))] (do_to (java/lang/Class::getDeclaredMethod (ffi.as_string "defineClass") signature (ffi.class_for java/lang/ClassLoader)) @@ -82,19 +82,19 @@ (def: .public (define class_name bytecode loader) (-> Text Binary java/lang/ClassLoader (Try java/lang/Object)) - (let [signature (array.of_list (list (:as java/lang/Object - class_name) - (:as java/lang/Object - bytecode) - (:as java/lang/Object - (|> 0 - (:as (Primitive "java.lang.Long")) - ffi.long_to_int)) - (:as java/lang/Object - (|> bytecode - binary.size - (:as (Primitive "java.lang.Long")) - ffi.long_to_int))))] + (let [signature (array.of_list (list (as java/lang/Object + class_name) + (as java/lang/Object + bytecode) + (as java/lang/Object + (|> 0 + (as (Primitive "java.lang.Long")) + ffi.long_to_int)) + (as java/lang/Object + (|> bytecode + binary.size + (as (Primitive "java.lang.Long")) + ffi.long_to_int))))] (java/lang/reflect/Method::invoke loader signature java/lang/ClassLoader::defineClass))) (def: .public (new_library _) @@ -114,13 +114,13 @@ (java/lang/ClassLoader (findClass self [class_name java/lang/String]) (java/lang/Class [? < java/lang/Object]) "throws" [java/lang/ClassNotFoundException] - (let [class_name (:as Text class_name) + (let [class_name (as Text class_name) classes (|> library atom.read! io.run!)] (case (dictionary.value class_name classes) {.#Some bytecode} (case (..define class_name bytecode (<| <cast> self)) {try.#Success class} - (:expected class) + (as_expected class) {try.#Failure error} (panic! (exception.error ..cannot_define [class_name error]))) diff --git a/stdlib/source/library/lux/target/jvm/modifier.lux b/stdlib/source/library/lux/target/jvm/modifier.lux index bf5d79aa2..24e442a21 100644 --- a/stdlib/source/library/lux/target/jvm/modifier.lux +++ b/stdlib/source/library/lux/target/jvm/modifier.lux @@ -1,52 +1,52 @@ (.using - [library - [lux "*" - [abstract - ["[0]" equivalence {"+" Equivalence}] - ["[0]" monoid {"+" Monoid}]] - [control - ["[0]" try] - ["<>" parser - ["<[0]>" code]]] - [data - [format - ["[0]F" binary {"+" Writer}]]] - [macro {"+" with_symbols} - [syntax {"+" syntax:}] - ["[0]" code]] - [math - ["[0]" number {"+" hex} - ["[0]" i64]]] - [type - abstract]]] - ["[0]" // "_" - [encoding - ["[1][0]" unsigned]]]) + [library + [lux "*" + [abstract + ["[0]" equivalence {"+" Equivalence}] + ["[0]" monoid {"+" Monoid}]] + [control + ["[0]" try] + ["<>" parser + ["<[0]>" code]]] + [data + [format + ["[0]F" binary {"+" Writer}]]] + [macro {"+" with_symbols} + [syntax {"+" syntax:}] + ["[0]" code]] + [math + ["[0]" number {"+" hex} + ["[0]" i64]]] + [type + [abstract {"-" pattern}]]]] + ["[0]" // "_" + [encoding + ["[1][0]" unsigned]]]) (abstract: .public (Modifier of) //unsigned.U2 (def: .public code (-> (Modifier Any) //unsigned.U2) - (|>> :representation)) + (|>> representation)) (implementation: .public equivalence (All (_ of) (Equivalence (Modifier of))) (def: (= reference sample) (# //unsigned.equivalence = - (:representation reference) - (:representation sample)))) + (representation reference) + (representation sample)))) (template: (!wrap value) [(|> value //unsigned.u2 try.trusted - :abstraction)]) + abstraction)]) (template: (!unwrap value) [(|> value - :representation + representation //unsigned.value)]) (def: .public (has? sub super) @@ -71,7 +71,7 @@ (def: .public writer (All (_ of) (Writer (Modifier of))) - (|>> :representation //unsigned.writer/2)) + (|>> representation //unsigned.writer/2)) (def: modifier (-> Nat Modifier) diff --git a/stdlib/source/library/lux/target/jvm/reflection.lux b/stdlib/source/library/lux/target/jvm/reflection.lux index c8daea629..29776163c 100644 --- a/stdlib/source/library/lux/target/jvm/reflection.lux +++ b/stdlib/source/library/lux/target/jvm/reflection.lux @@ -133,7 +133,7 @@ (<| (case (ffi.check java/lang/Class reflection) {.#Some class} (let [class_name (|> class - (:as (java/lang/Class java/lang/Object)) + (as (java/lang/Class java/lang/Object)) java/lang/Class::getName)] (`` (if (or (~~ (template [<reflection>] [(text#= (/reflection.reflection <reflection>) @@ -162,7 +162,7 @@ (array.list {.#None}) (monad.each ! parameter) (# ! each (/.class (|> raw' - (:as (java/lang/Class java/lang/Object)) + (as (java/lang/Class java/lang/Object)) java/lang/Class::getName))) (exception.with ..cannot_convert_to_a_lux_type [reflection]))) @@ -224,7 +224,7 @@ (<| (case (ffi.check java/lang/Class reflection) {.#Some reflection} (let [class_name (|> reflection - (:as (java/lang/Class java/lang/Object)) + (as (java/lang/Class java/lang/Object)) java/lang/Class::getName)] (`` (cond (~~ (template [<reflection> <type>] [(text#= (/reflection.reflection <reflection>) @@ -257,7 +257,7 @@ (case (ffi.check java/lang/Class reflection) {.#Some class} (let [class_name (|> reflection - (:as (java/lang/Class java/lang/Object)) + (as (java/lang/Class java/lang/Object)) java/lang/Class::getName)] (if (text#= (/reflection.reflection /reflection.void) class_name) diff --git a/stdlib/source/library/lux/target/jvm/type.lux b/stdlib/source/library/lux/target/jvm/type.lux index c4de519c3..4343e6ff0 100644 --- a/stdlib/source/library/lux/target/jvm/type.lux +++ b/stdlib/source/library/lux/target/jvm/type.lux @@ -1,29 +1,29 @@ (.using - [library - [lux {"-" Primitive Type int char} - [abstract - [equivalence {"+" Equivalence}] - [hash {"+" Hash}]] - [control - ["[0]" maybe]] - [data - ["[0]" text - ["%" format {"+" Format}]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [math - [number - ["n" nat]]] - [type - abstract]]] - ["[0]" // "_" - [encoding - ["[1][0]" name {"+" External}]]] - ["[0]" / "_" - [category {"+" Void Value' Value Return' Return Method Primitive Object Class Array Var Parameter Declaration}] - ["[1][0]" signature {"+" Signature}] - ["[1][0]" descriptor {"+" Descriptor}] - ["[1][0]" reflection {"+" Reflection}]]) + [library + [lux {"-" Primitive Type int char} + [abstract + [equivalence {"+" Equivalence}] + [hash {"+" Hash}]] + [control + ["[0]" maybe]] + [data + ["[0]" text + ["%" format {"+" Format}]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [math + [number + ["n" nat]]] + [type + [abstract {"-" pattern}]]]] + ["[0]" // "_" + [encoding + ["[1][0]" name {"+" External}]]] + ["[0]" / "_" + [category {"+" Void Value' Value Return' Return Method Primitive Object Class Array Var Parameter Declaration}] + ["[1][0]" signature {"+" Signature}] + ["[1][0]" descriptor {"+" Descriptor}] + ["[1][0]" reflection {"+" Reflection}]]) (abstract: .public (Type category) [(Signature category) @@ -45,7 +45,7 @@ (template [<name> <style>] [(def: .public (<name> type) (All (_ category) (-> (Type category) (<style> category))) - (let [[signature descriptor reflection] (:representation type)] + (let [[signature descriptor reflection] (representation type)] <name>))] [signature Signature] @@ -56,13 +56,13 @@ (All (_ category) (-> (Type (<| Return' Value' category)) (Reflection (<| Return' Value' category)))) - (let [[signature descriptor reflection] (:representation type)] + (let [[signature descriptor reflection] (representation type)] reflection)) (template [<category> <name> <signature> <descriptor> <reflection>] [(def: .public <name> (Type <category>) - (:abstraction [<signature> <descriptor> <reflection>]))] + (abstraction [<signature> <descriptor> <reflection>]))] [Void void /signature.void /descriptor.void /reflection.void] [Primitive boolean /signature.boolean /descriptor.boolean /reflection.boolean] @@ -77,59 +77,59 @@ (def: .public (array type) (-> (Type Value) (Type Array)) - (:abstraction + (abstraction [(/signature.array (..signature type)) (/descriptor.array (..descriptor type)) (/reflection.array (..reflection type))])) (def: .public (class name parameters) (-> External (List (Type Parameter)) (Type Class)) - (:abstraction + (abstraction [(/signature.class name (list#each ..signature parameters)) (/descriptor.class name) (/reflection.class name)])) (def: .public (declaration name variables) (-> External (List (Type Var)) (Type Declaration)) - (:abstraction + (abstraction [(/signature.declaration name (list#each ..signature variables)) (/descriptor.declaration name) (/reflection.declaration name)])) (def: .public (as_class type) (-> (Type Declaration) (Type Class)) - (:abstraction - (let [[signature descriptor reflection] (:representation type)] + (abstraction + (let [[signature descriptor reflection] (representation type)] [(/signature.as_class signature) (/descriptor.as_class descriptor) (/reflection.as_class reflection)]))) (def: .public wildcard (Type Parameter) - (:abstraction + (abstraction [/signature.wildcard /descriptor.wildcard /reflection.wildcard])) (def: .public (var name) (-> Text (Type Var)) - (:abstraction + (abstraction [(/signature.var name) /descriptor.var /reflection.var])) (def: .public (lower bound) (-> (Type Parameter) (Type Parameter)) - (:abstraction - (let [[signature descriptor reflection] (:representation bound)] + (abstraction + (let [[signature descriptor reflection] (representation bound)] [(/signature.lower signature) (/descriptor.lower descriptor) (/reflection.lower reflection)]))) (def: .public (upper bound) (-> (Type Parameter) (Type Parameter)) - (:abstraction - (let [[signature descriptor reflection] (:representation bound)] + (abstraction + (let [[signature descriptor reflection] (representation bound)] [(/signature.upper signature) (/descriptor.upper descriptor) (/reflection.upper reflection)]))) @@ -140,14 +140,14 @@ (Type Return) (List (Type Class))] (Type Method)) - (:abstraction + (abstraction [(/signature.method [(list#each ..signature type_variables) (list#each ..signature inputs) (..signature output) (list#each ..signature exceptions)]) (/descriptor.method [(list#each ..descriptor inputs) (..descriptor output)]) - (:expected ..void)])) + (as_expected ..void)])) (implementation: .public equivalence (All (_ category) (Equivalence (Type category))) @@ -167,7 +167,7 @@ (-> (Type Value) (Either (Type Object) (Type Primitive))) (if (`` (or (~~ (template [<type>] - [(# ..equivalence = (: (Type Value) <type>) type)] + [(# ..equivalence = (is (Type Value) <type>) type)] [..boolean] [..byte] @@ -177,18 +177,18 @@ [..float] [..double] [..char])))) - (|> type (:as (Type Primitive)) {.#Right}) - (|> type (:as (Type Object)) {.#Left}))) + (|> type (as (Type Primitive)) {.#Right}) + (|> type (as (Type Object)) {.#Left}))) (def: .public (void? type) (-> (Type Return) (Either (Type Value) (Type Void))) (if (`` (or (~~ (template [<type>] - [(# ..equivalence = (: (Type Return) <type>) type)] + [(# ..equivalence = (is (Type Return) <type>) type)] [..void])))) - (|> type (:as (Type Void)) {.#Right}) - (|> type (:as (Type Value)) {.#Left}))) + (|> type (as (Type Void)) {.#Right}) + (|> type (as (Type Value)) {.#Left}))) ) (def: .public (class? type) diff --git a/stdlib/source/library/lux/target/jvm/type/category.lux b/stdlib/source/library/lux/target/jvm/type/category.lux index 45128d756..0b740dae1 100644 --- a/stdlib/source/library/lux/target/jvm/type/category.lux +++ b/stdlib/source/library/lux/target/jvm/type/category.lux @@ -1,10 +1,10 @@ (.using - [library - [lux {"-" Primitive} - [macro - ["[0]" template]] - [type - abstract]]]) + [library + [lux {"-" Primitive} + [macro + ["[0]" template]] + [type + [abstract {"-" pattern}]]]]) (abstract: Void' Any) (abstract: .public (Value' kind) Any) diff --git a/stdlib/source/library/lux/target/jvm/type/descriptor.lux b/stdlib/source/library/lux/target/jvm/type/descriptor.lux index d09a5d94f..c8c8f6f49 100644 --- a/stdlib/source/library/lux/target/jvm/type/descriptor.lux +++ b/stdlib/source/library/lux/target/jvm/type/descriptor.lux @@ -1,37 +1,37 @@ (.using - [library - [lux {"-" Primitive int char} - [abstract - [equivalence {"+" Equivalence}]] - [control - ["[0]" maybe]] - [data - ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [math - [number - ["n" nat]]] - [type - abstract]]] - ["[0]" // "_" - [category {"+" Void Value Return Method Primitive Object Class Array Var Parameter Declaration}] - ["/[1]" // "_" - [encoding - ["[1][0]" name {"+" Internal External}]]]]) + [library + [lux {"-" Primitive int char} + [abstract + [equivalence {"+" Equivalence}]] + [control + ["[0]" maybe]] + [data + ["[0]" text ("[1]#[0]" equivalence) + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [math + [number + ["n" nat]]] + [type + [abstract {"-" pattern}]]]] + ["[0]" // "_" + [category {"+" Void Value Return Method Primitive Object Class Array Var Parameter Declaration}] + ["/[1]" // "_" + [encoding + ["[1][0]" name {"+" Internal External}]]]]) (abstract: .public (Descriptor category) Text (def: .public descriptor (-> (Descriptor Any) Text) - (|>> :representation)) + (|>> representation)) (template [<sigil> <category> <name>] [(def: .public <name> (Descriptor <category>) - (:abstraction <sigil>))] + (abstraction <sigil>))] ["V" Void void] ["Z" Primitive boolean] @@ -52,20 +52,20 @@ (|>> ///name.internal ///name.read (text.enclosed [..class_prefix ..class_suffix]) - :abstraction)) + abstraction)) (def: .public (declaration name) (-> External (Descriptor Declaration)) - (:transmutation (..class name))) + (transmutation (..class name))) (def: .public as_class (-> (Descriptor Declaration) (Descriptor Class)) - (|>> :transmutation)) + (|>> transmutation)) (template [<name> <category>] [(def: .public <name> (Descriptor <category>) - (:transmutation + (transmutation (..class "java.lang.Object")))] [var Var] @@ -78,40 +78,40 @@ (def: .public upper (-> (Descriptor Parameter) (Descriptor Parameter)) - (|>> :transmutation)) + (|>> transmutation)) (def: .public array_prefix "[") (def: .public array (-> (Descriptor Value) (Descriptor Array)) - (|>> :representation + (|>> representation (format ..array_prefix) - :abstraction)) + abstraction)) (def: .public (method [inputs output]) (-> [(List (Descriptor Value)) (Descriptor Return)] (Descriptor Method)) - (:abstraction + (abstraction (format (|> inputs (list#each ..descriptor) text.together (text.enclosed ["(" ")"])) - (:representation output)))) + (representation output)))) (implementation: .public equivalence (All (_ category) (Equivalence (Descriptor category))) (def: (= parameter subject) - (text#= (:representation parameter) (:representation subject)))) + (text#= (representation parameter) (representation subject)))) (def: .public class_name (-> (Descriptor Object) Internal) (let [prefix_size (text.size ..class_prefix) suffix_size (text.size ..class_suffix)] (function (_ descriptor) - (let [repr (:representation descriptor)] + (let [repr (representation descriptor)] (if (text.starts_with? ..array_prefix repr) (///name.internal repr) (|> repr diff --git a/stdlib/source/library/lux/target/jvm/type/parser.lux b/stdlib/source/library/lux/target/jvm/type/parser.lux index 8c896e9f1..a1bea32fc 100644 --- a/stdlib/source/library/lux/target/jvm/type/parser.lux +++ b/stdlib/source/library/lux/target/jvm/type/parser.lux @@ -221,18 +221,18 @@ (List (Type Value)) (Type Return) (List (Type Class))]) - (let [parser (: (Parser [(List (Type Var)) - (List (Type Value)) - (Type Return) - (List (Type Class))]) - ($_ <>.and - (|> (<>.some (<>#each product.left ..var_declaration)) - (<>.after (<text>.this //signature.parameters_start)) - (<>.before (<text>.this //signature.parameters_end)) - (<>.else (list))) - ..inputs - ..return - (<>.some ..exception)))] + (let [parser (is (Parser [(List (Type Var)) + (List (Type Value)) + (Type Return) + (List (Type Class))]) + ($_ <>.and + (|> (<>.some (<>#each product.left ..var_declaration)) + (<>.after (<text>.this //signature.parameters_start)) + (<>.before (<text>.this //signature.parameters_end)) + (<>.else (list))) + ..inputs + ..return + (<>.some ..exception)))] (|>> //.signature //signature.signature (<text>.result parser) diff --git a/stdlib/source/library/lux/target/jvm/type/reflection.lux b/stdlib/source/library/lux/target/jvm/type/reflection.lux index f4df7e88b..37d7e0dde 100644 --- a/stdlib/source/library/lux/target/jvm/type/reflection.lux +++ b/stdlib/source/library/lux/target/jvm/type/reflection.lux @@ -1,37 +1,37 @@ (.using - [library - [lux {"-" Primitive int char} - [abstract - [equivalence {"+" Equivalence}]] - [data - ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}]]] - [type - abstract]]] - ["[0]" // "_" - [category {"+" Void Value Return Method Primitive Object Class Array Var Parameter Declaration}] - ["[1][0]" descriptor] - [// - [encoding - ["[1][0]" name {"+" External}]]]]) + [library + [lux {"-" Primitive int char} + [abstract + [equivalence {"+" Equivalence}]] + [data + ["[0]" text ("[1]#[0]" equivalence) + ["%" format {"+" format}]]] + [type + [abstract {"-" pattern}]]]] + ["[0]" // "_" + [category {"+" Void Value Return Method Primitive Object Class Array Var Parameter Declaration}] + ["[1][0]" descriptor] + [// + [encoding + ["[1][0]" name {"+" External}]]]]) (abstract: .public (Reflection category) Text (def: .public reflection (-> (Reflection Any) Text) - (|>> :representation)) + (|>> representation)) (implementation: .public equivalence (All (_ category) (Equivalence (Reflection category))) (def: (= parameter subject) - (text#= (:representation parameter) (:representation subject)))) + (text#= (representation parameter) (representation subject)))) (template [<category> <name> <reflection>] [(def: .public <name> (Reflection <category>) - (:abstraction <reflection>))] + (abstraction <reflection>))] [Void void "void"] [Primitive boolean "boolean"] @@ -46,19 +46,19 @@ (def: .public class (-> External (Reflection Class)) - (|>> :abstraction)) + (|>> abstraction)) (def: .public (declaration name) (-> External (Reflection Declaration)) - (:transmutation (..class name))) + (transmutation (..class name))) (def: .public as_class (-> (Reflection Declaration) (Reflection Class)) - (|>> :transmutation)) + (|>> transmutation)) (def: .public (array element) (-> (Reflection Value) (Reflection Array)) - (let [element' (:representation element) + (let [element' (representation element) elementR (`` (cond (text.starts_with? //descriptor.array_prefix element') element' @@ -82,12 +82,12 @@ //name.external_separator))))] (|> elementR (format //descriptor.array_prefix) - :abstraction))) + abstraction))) (template [<name> <category>] [(def: .public <name> (Reflection <category>) - (:transmutation + (transmutation (..class "java.lang.Object")))] [var Var] @@ -100,5 +100,5 @@ (def: .public upper (-> (Reflection Parameter) (Reflection Parameter)) - (|>> :transmutation)) + (|>> transmutation)) ) diff --git a/stdlib/source/library/lux/target/jvm/type/signature.lux b/stdlib/source/library/lux/target/jvm/type/signature.lux index e2b00d292..a5b710c59 100644 --- a/stdlib/source/library/lux/target/jvm/type/signature.lux +++ b/stdlib/source/library/lux/target/jvm/type/signature.lux @@ -12,7 +12,7 @@ [collection ["[0]" list ("[1]#[0]" functor)]]] [type - abstract]]] + [abstract {"-" pattern}]]]] ["[0]" // "_" [category {"+" Void Value Return Method Primitive Object Class Array Var Parameter Declaration Inheritance}] ["[1][0]" descriptor] @@ -25,12 +25,12 @@ (def: .public signature (-> (Signature Any) Text) - (|>> :representation)) + (|>> representation)) (template [<category> <name> <descriptor>] [(def: .public <name> (Signature <category>) - (:abstraction (//descriptor.descriptor <descriptor>)))] + (abstraction (//descriptor.descriptor <descriptor>)))] [Void void //descriptor.void] [Primitive boolean //descriptor.boolean] @@ -45,13 +45,13 @@ (def: .public array (-> (Signature Value) (Signature Array)) - (|>> :representation + (|>> representation (format //descriptor.array_prefix) - :abstraction)) + abstraction)) (def: .public wildcard (Signature Parameter) - (:abstraction "*")) + (abstraction "*")) (template [<char> <name>] [(def: .public <name> <char>)] @@ -72,7 +72,7 @@ (template [<name> <prefix>] [(def: .public <name> (-> (Signature Parameter) (Signature Parameter)) - (|>> :representation (format <prefix>) :abstraction))] + (|>> representation (format <prefix>) abstraction))] [lower ..lower_prefix] [upper ..upper_prefix] @@ -81,17 +81,17 @@ (def: .public var (-> Text (Signature Var)) (|>> (text.enclosed [..var_prefix //descriptor.class_suffix]) - :abstraction)) + abstraction)) (def: .public var_name (-> (Signature Var) Text) - (|>> :representation + (|>> representation (text.replaced ..var_prefix "") (text.replaced //descriptor.class_suffix ""))) (def: .public (class name parameters) (-> External (List (Signature Parameter)) (Signature Class)) - (:abstraction + (abstraction (format //descriptor.class_prefix (|> name ///name.internal ///name.read) (case parameters @@ -108,7 +108,7 @@ (def: .public (declaration name variables) (-> External (List (Signature Var)) (Signature Declaration)) - (:transmutation (..class name variables))) + (transmutation (..class name variables))) (def: class_bound (|> (..class "java.lang.Object" (list)) @@ -138,16 +138,16 @@ (def: .public (inheritance variables super interfaces) (-> (List (Signature Var)) (Signature Class) (List (Signature Class)) (Signature Inheritance)) - (:abstraction + (abstraction (format (var_declaration/* variables) - (:representation super) + (representation super) (|> interfaces (list#each ..signature) text.together)))) (def: .public as_class (-> (Signature Declaration) (Signature Class)) - (|>> :transmutation)) + (|>> transmutation)) (def: .public (method [type_variables inputs output exceptions]) (-> [(List (Signature Var)) @@ -155,28 +155,28 @@ (Signature Return) (List (Signature Class))] (Signature Method)) - (:abstraction + (abstraction (format (var_declaration/* type_variables) (|> inputs (list#each ..signature) text.together (text.enclosed [..arguments_start ..arguments_end])) - (:representation output) + (representation output) (|> exceptions - (list#each (|>> :representation (format ..exception_prefix))) + (list#each (|>> representation (format ..exception_prefix))) text.together)))) (implementation: .public equivalence (All (_ category) (Equivalence (Signature category))) (def: (= parameter subject) - (text#= (:representation parameter) - (:representation subject)))) + (text#= (representation parameter) + (representation subject)))) (implementation: .public hash (All (_ category) (Hash (Signature category))) (def: &equivalence ..equivalence) - (def: hash (|>> :representation text#hash))) + (def: hash (|>> representation text#hash))) ) diff --git a/stdlib/source/library/lux/target/lua.lux b/stdlib/source/library/lux/target/lua.lux index 069e5d2a7..2269e015b 100644 --- a/stdlib/source/library/lux/target/lua.lux +++ b/stdlib/source/library/lux/target/lua.lux @@ -25,7 +25,7 @@ ["i" int] ["f" frac]]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) ... Added the carriage return for better Windows compatibility. (def: \n+ @@ -47,21 +47,21 @@ (All (_ brand) (Equivalence (Code brand))) (def: (= reference subject) - (# text.equivalence = (:representation reference) (:representation subject)))) + (# text.equivalence = (representation reference) (representation subject)))) (implementation: .public hash (All (_ brand) (Hash (Code brand))) (def: &equivalence ..equivalence) - (def: hash (|>> :representation (# text.hash hash)))) + (def: hash (|>> representation (# text.hash hash)))) (def: .public manual (-> Text Code) - (|>> :abstraction)) + (|>> abstraction)) (def: .public code (-> (Code Any) Text) - (|>> :representation)) + (|>> representation)) (template [<type> <super>+] [(with_expansions [<brand> (template.symbol [<type> "'"])] @@ -87,14 +87,14 @@ (def: .public nil Literal - (:abstraction "nil")) + (abstraction "nil")) (def: .public boolean (-> Bit Literal) (|>> (pipe.case #0 "false" #1 "true") - :abstraction)) + abstraction)) (def: .public int (-> Int Literal) @@ -104,7 +104,7 @@ (|>> .nat to_hex (format "0x") - :abstraction))) + abstraction))) (def: .public float (-> Frac Literal) @@ -119,7 +119,7 @@ ... else [%.frac (text.replaced "+" "")]) - :abstraction)) + abstraction)) (def: safe (-> Text Text) @@ -140,42 +140,42 @@ (def: .public string (-> Text Literal) - (|>> ..safe (text.enclosed' text.double_quote) :abstraction)) + (|>> ..safe (text.enclosed' text.double_quote) abstraction)) (def: .public multi (-> (List Expression) Expression) (|>> (list#each ..code) (text.interposed ..input_separator) - :abstraction)) + abstraction)) (def: .public array (-> (List Expression) Literal) (|>> (list#each ..code) (text.interposed ..input_separator) (text.enclosed ["{" "}"]) - :abstraction)) + abstraction)) (def: .public table (-> (List [Text Expression]) Literal) (|>> (list#each (.function (_ [key value]) - (format key " = " (:representation value)))) + (format key " = " (representation value)))) (text.interposed ..input_separator) (text.enclosed ["({" "})"]) - :abstraction)) + abstraction)) (def: .public (item idx array) (-> Expression Expression Access) - (:abstraction (format "(" (:representation array) ")[" (:representation idx) "]"))) + (abstraction (format "(" (representation array) ")[" (representation idx) "]"))) (def: .public (the field table) (-> Text Expression Access) - (:abstraction (format (:representation table) "." field))) + (abstraction (format (representation table) "." field))) (def: .public length (-> Expression Computation) - (|>> :representation + (|>> representation (text.enclosed ["#(" ")"]) - :abstraction)) + abstraction)) (def: .public (apply args func) (-> (List Expression) Expression Computation) @@ -183,8 +183,8 @@ (list#each ..code) (text.interposed ..input_separator) (text.enclosed ["(" ")"]) - (format (:representation func)) - :abstraction)) + (format (representation func)) + abstraction)) (def: .public (do method args table) (-> Text (List Expression) Expression Computation) @@ -192,17 +192,17 @@ (list#each ..code) (text.interposed ..input_separator) (text.enclosed ["(" ")"]) - (format (:representation table) ":" method) - :abstraction)) + (format (representation table) ":" method) + abstraction)) (template [<op> <name>] [(def: .public (<name> parameter subject) (-> Expression Expression Expression) - (:abstraction (format "(" - (:representation subject) - " " <op> " " - (:representation parameter) - ")")))] + (abstraction (format "(" + (representation subject) + " " <op> " " + (representation parameter) + ")")))] ["==" =] ["<" <] @@ -231,7 +231,7 @@ (template [<name> <unary>] [(def: .public (<name> subject) (-> Expression Expression) - (:abstraction (format "(" <unary> " " (:representation subject) ")")))] + (abstraction (format "(" <unary> " " (representation subject) ")")))] [not "not"] [opposite "-"] @@ -240,7 +240,7 @@ (template [<name> <type>] [(def: .public <name> (-> Text <type>) - (|>> :abstraction))] + (|>> abstraction))] [var Var] [label Label] @@ -248,14 +248,14 @@ (def: .public statement (-> Expression Statement) - (|>> :representation :abstraction)) + (|>> representation abstraction)) (def: .public (then pre! post!) (-> Statement Statement Statement) - (:abstraction - (format (:representation pre!) + (abstraction + (format (representation pre!) \n+ - (:representation post!)))) + (representation post!)))) (def: locations (-> (List Location) Text) @@ -264,91 +264,91 @@ (def: .public (local vars) (-> (List Var) Statement) - (:abstraction (format "local " (..locations vars)))) + (abstraction (format "local " (..locations vars)))) (def: .public (set vars value) (-> (List Location) Expression Statement) - (:abstraction (format (..locations vars) " = " (:representation value)))) + (abstraction (format (..locations vars) " = " (representation value)))) (def: .public (let vars value) (-> (List Var) Expression Statement) - (:abstraction (format "local " (..locations vars) " = " (:representation value)))) + (abstraction (format "local " (..locations vars) " = " (representation value)))) (def: .public (local/1 var value) (-> Var Expression Statement) - (:abstraction (format "local " (:representation var) " = " (:representation value)))) + (abstraction (format "local " (representation var) " = " (representation value)))) (def: .public (if test then! else!) (-> Expression Statement Statement Statement) - (:abstraction (format "if " (:representation test) - \n+ "then" (..nested (:representation then!)) - \n+ "else" (..nested (:representation else!)) - \n+ "end"))) + (abstraction (format "if " (representation test) + \n+ "then" (..nested (representation then!)) + \n+ "else" (..nested (representation else!)) + \n+ "end"))) (def: .public (when test then!) (-> Expression Statement Statement) - (:abstraction (format "if " (:representation test) - \n+ "then" (..nested (:representation then!)) - \n+ "end"))) + (abstraction (format "if " (representation test) + \n+ "then" (..nested (representation then!)) + \n+ "end"))) (def: .public (while test body!) (-> Expression Statement Statement) - (:abstraction - (format "while " (:representation test) " do" - (..nested (:representation body!)) + (abstraction + (format "while " (representation test) " do" + (..nested (representation body!)) \n+ "end"))) (def: .public (repeat until body!) (-> Expression Statement Statement) - (:abstraction + (abstraction (format "repeat" - (..nested (:representation body!)) - \n+ "until " (:representation until)))) + (..nested (representation body!)) + \n+ "until " (representation until)))) (def: .public (for_in vars source body!) (-> (List Var) Expression Statement Statement) - (:abstraction + (abstraction (format "for " (|> vars (list#each ..code) (text.interposed ..input_separator)) - " in " (:representation source) " do" - (..nested (:representation body!)) + " in " (representation source) " do" + (..nested (representation body!)) \n+ "end"))) (def: .public (for_step var from to step body!) (-> Var Expression Expression Expression Statement Statement) - (:abstraction - (format "for " (:representation var) - " = " (:representation from) - ..input_separator (:representation to) - ..input_separator (:representation step) " do" - (..nested (:representation body!)) + (abstraction + (format "for " (representation var) + " = " (representation from) + ..input_separator (representation to) + ..input_separator (representation step) " do" + (..nested (representation body!)) \n+ "end"))) (def: .public (return value) (-> Expression Statement) - (:abstraction (format "return " (:representation value)))) + (abstraction (format "return " (representation value)))) (def: .public (closure args body!) (-> (List Var) Statement Expression) (|> (format "function " (|> args ..locations (text.enclosed ["(" ")"])) - (..nested (:representation body!)) + (..nested (representation body!)) \n+ "end") (text.enclosed ["(" ")"]) - :abstraction)) + abstraction)) (template [<name> <code> <binding>] [(def: .public (<name> name args body!) (-> <binding> (List Var) Statement Statement) - (:abstraction - (format <code> " " (:representation name) + (abstraction + (format <code> " " (representation name) (|> args ..locations (text.enclosed ["(" ")"])) - (..nested (:representation body!)) + (..nested (representation body!)) \n+ "end")))] [function "function" Location] @@ -357,20 +357,20 @@ (def: .public break Statement - (:abstraction "break")) + (abstraction "break")) (def: .public (set_label label) (-> Label Statement) - (:abstraction (format "::" (:representation label) "::"))) + (abstraction (format "::" (representation label) "::"))) (def: .public (go_to label) (-> Label Statement) - (:abstraction (format "goto " (:representation label)))) + (abstraction (format "goto " (representation label)))) ... https://www.lua.org/pil/1.3.html (def: .public (comment commentary on) (All (_ kind) (-> Text (Code kind) (Code kind))) - (:abstraction (format "-- " commentary \n+ (:representation on)))) + (abstraction (format "-- " commentary \n+ (representation on)))) ) (syntax: (arity_inputs [arity <code>.nat]) diff --git a/stdlib/source/library/lux/target/php.lux b/stdlib/source/library/lux/target/php.lux index 6f5b171c9..1dd67843b 100644 --- a/stdlib/source/library/lux/target/php.lux +++ b/stdlib/source/library/lux/target/php.lux @@ -24,7 +24,7 @@ ["n" nat] ["f" frac]]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) (def: input_separator ", ") (def: statement_suffix ";") @@ -55,21 +55,21 @@ (All (_ brand) (Equivalence (Code brand))) (def: (= reference subject) - (# text.equivalence = (:representation reference) (:representation subject)))) + (# text.equivalence = (representation reference) (representation subject)))) (implementation: .public hash (All (_ brand) (Hash (Code brand))) (def: &equivalence ..equivalence) - (def: hash (|>> :representation (# text.hash hash)))) + (def: hash (|>> representation (# text.hash hash)))) (def: .public manual (-> Text Code) - (|>> :abstraction)) + (|>> abstraction)) (def: .public code (-> (Code Any) Text) - (|>> :representation)) + (|>> representation)) (template [<type> <super>+] [(with_expansions [<brand> (template.symbol [<type> "'"])] @@ -102,18 +102,18 @@ (def: .public ; (-> Expression Statement) - (|>> :representation + (|>> representation (text.suffix ..statement_suffix) - :abstraction)) + abstraction)) (def: .public var (-> Text Var) - (|>> (format "$") :abstraction)) + (|>> (format "$") abstraction)) (template [<name> <type>] [(def: .public <name> (-> Text <type>) - (|>> :abstraction))] + (|>> abstraction))] [constant Constant] [label Label] @@ -121,23 +121,23 @@ (def: .public (set_label label) (-> Label Statement) - (:abstraction (format (:representation label) ":"))) + (abstraction (format (representation label) ":"))) (def: .public (go_to label) (-> Label Statement) - (:abstraction - (format "goto " (:representation label) ..statement_suffix))) + (abstraction + (format "goto " (representation label) ..statement_suffix))) (def: .public null Literal - (:abstraction "NULL")) + (abstraction "NULL")) (def: .public bool (-> Bit Literal) (|>> (pipe.case #0 "false" #1 "true") - :abstraction)) + abstraction)) (def: .public int (-> Int Literal) @@ -145,7 +145,7 @@ (|>> .nat to_hex (format "0x") - :abstraction))) + abstraction))) (def: .public float (-> Frac Literal) @@ -160,7 +160,7 @@ ... else [%.frac]) - :abstraction)) + abstraction)) (def: safe (-> Text Text) @@ -184,7 +184,7 @@ (-> Text Literal) (|>> ..safe (text.enclosed [text.double_quote text.double_quote]) - :abstraction)) + abstraction)) (def: arguments (-> (List Expression) Text) @@ -192,8 +192,8 @@ (def: .public (apply/* args func) (-> (List Expression) Expression Computation) - (|> (format (:representation func) (..arguments args)) - :abstraction)) + (|> (format (representation func) (..arguments args)) + abstraction)) ... TODO: Remove when no longer using JPHP. (def: .public (apply/*' args func) @@ -204,8 +204,8 @@ (-> (List Argument) Text) (|>> (list#each (function (_ [reference? var]) (.if reference? - (format "&" (:representation var)) - (:representation var)))) + (format "&" (representation var)) + (representation var)))) (text.interposed ..input_separator) ..group)) @@ -228,9 +228,9 @@ (format "use " (..parameters uses)))] (|> (format "function " (..parameters arguments) " " uses " " - (..block (:representation body!))) + (..block (representation body!))) ..group - :abstraction))) + abstraction))) (syntax: (arity_inputs [arity <code>.nat]) (in (case arity @@ -309,7 +309,7 @@ (def: .public (key_value key value) (-> Expression Expression Expression) - (:abstraction (format (:representation key) " => " (:representation value)))) + (abstraction (format (representation key) " => " (representation value)))) (def: .public (array/* values) (-> (List Expression) Literal) @@ -318,7 +318,7 @@ (text.interposed ..input_separator) ..group (format "array") - :abstraction)) + abstraction)) (def: .public (array_merge/+ required optionals) (-> Expression (List Expression) Computation) @@ -328,51 +328,51 @@ (-> (List [Expression Expression]) Literal) (|> kvs (list#each (function (_ [key value]) - (format (:representation key) " => " (:representation value)))) + (format (representation key) " => " (representation value)))) (text.interposed ..input_separator) ..group (format "array") - :abstraction)) + abstraction)) (def: .public (new constructor inputs) (-> Constant (List Expression) Computation) - (|> (format "new " (:representation constructor) (arguments inputs)) - :abstraction)) + (|> (format "new " (representation constructor) (arguments inputs)) + abstraction)) (def: .public (the field object) (-> Text Expression Computation) - (|> (format (:representation object) "->" field) - :abstraction)) + (|> (format (representation object) "->" field) + abstraction)) (def: .public (do method inputs object) (-> Text (List Expression) Expression Computation) - (|> (format (:representation (..the method object)) + (|> (format (representation (..the method object)) (..arguments inputs)) - :abstraction)) + abstraction)) (def: .public (item idx array) (-> Expression Expression Access) - (|> (format (:representation array) "[" (:representation idx) "]") - :abstraction)) + (|> (format (representation array) "[" (representation idx) "]") + abstraction)) (def: .public (global name) (-> Text Global) - (|> (..var "GLOBALS") (..item (..string name)) :transmutation)) + (|> (..var "GLOBALS") (..item (..string name)) transmutation)) (def: .public (? test then else) (-> Expression Expression Expression Computation) - (|> (format (..group (:representation test)) " ? " - (..group (:representation then)) " : " - (..group (:representation else))) + (|> (format (..group (representation test)) " ? " + (..group (representation then)) " : " + (..group (representation else))) ..group - :abstraction)) + abstraction)) (template [<name> <op>] [(def: .public (<name> parameter subject) (-> Expression Expression Computation) - (|> (format (:representation subject) " " <op> " " (:representation parameter)) + (|> (format (representation subject) " " <op> " " (representation parameter)) ..group - :abstraction))] + abstraction))] [or "||"] [and "&&"] @@ -398,7 +398,7 @@ (template [<unary> <name>] [(def: .public <name> (-> Computation Computation) - (|>> :representation (format <unary>) :abstraction))] + (|>> representation (format <unary>) abstraction))] ["!" not] ["~" bit_not] @@ -407,13 +407,13 @@ (def: .public (set var value) (-> Location Expression Computation) - (|> (format (:representation var) " = " (:representation value)) + (|> (format (representation var) " = " (representation value)) ..group - :abstraction)) + abstraction)) (def: .public (set! var value) (-> Location Expression Statement) - (:abstraction (format (:representation var) " = " (:representation value) ";"))) + (abstraction (format (representation var) " = " (representation value) ";"))) (def: .public (set? var) (-> Var Computation) @@ -422,7 +422,7 @@ (template [<name> <modifier>] [(def: .public <name> (-> Var Statement) - (|>> :representation (format <modifier> " ") (text.suffix ..statement_suffix) :abstraction))] + (|>> representation (format <modifier> " ") (text.suffix ..statement_suffix) abstraction))] [define_global "global"] ) @@ -430,9 +430,9 @@ (template [<name> <modifier> <location>] [(def: .public (<name> location value) (-> <location> Expression Statement) - (:abstraction (format <modifier> " " (:representation location) - " = " (:representation value) - ..statement_suffix)))] + (abstraction (format <modifier> " " (representation location) + " = " (representation value) + ..statement_suffix)))] [define_static "static" Var] [define_constant "const" Constant] @@ -440,44 +440,44 @@ (def: .public (if test then! else!) (-> Expression Statement Statement Statement) - (:abstraction - (format "if" (..group (:representation test)) " " - (..block (:representation then!)) + (abstraction + (format "if" (..group (representation test)) " " + (..block (representation then!)) " else " - (..block (:representation else!))))) + (..block (representation else!))))) (def: .public (when test then!) (-> Expression Statement Statement) - (:abstraction - (format "if" (..group (:representation test)) " " - (..block (:representation then!))))) + (abstraction + (format "if" (..group (representation test)) " " + (..block (representation then!))))) (def: .public (then pre! post!) (-> Statement Statement Statement) - (:abstraction - (format (:representation pre!) + (abstraction + (format (representation pre!) \n+ - (:representation post!)))) + (representation post!)))) (def: .public (while test body!) (-> Expression Statement Statement) - (:abstraction - (format "while" (..group (:representation test)) " " - (..block (:representation body!))))) + (abstraction + (format "while" (..group (representation test)) " " + (..block (representation body!))))) (def: .public (do_while test body!) (-> Expression Statement Statement) - (:abstraction - (format "do " (..block (:representation body!)) - " while" (..group (:representation test)) + (abstraction + (format "do " (..block (representation body!)) + " while" (..group (representation test)) ..statement_suffix))) (def: .public (for_each array value body!) (-> Expression Var Statement Statement) - (:abstraction - (format "foreach(" (:representation array) - " as " (:representation value) - ") " (..block (:representation body!))))) + (abstraction + (format "foreach(" (representation array) + " as " (representation value) + ") " (..block (representation body!))))) (type: .public Except (Record @@ -487,15 +487,15 @@ (def: (catch except) (-> Except Text) - (let [declaration (format (:representation (.the #class except)) - " " (:representation (.the #exception except)))] + (let [declaration (format (representation (.the #class except)) + " " (representation (.the #exception except)))] (format "catch" (..group declaration) " " - (..block (:representation (.the #handler except)))))) + (..block (representation (.the #handler except)))))) (def: .public (try body! excepts) (-> Statement (List Except) Statement) - (:abstraction - (format "try " (..block (:representation body!)) + (abstraction + (format "try " (..block (representation body!)) \n+ (|> excepts (list#each catch) @@ -504,7 +504,7 @@ (template [<name> <keyword>] [(def: .public <name> (-> Expression Statement) - (|>> :representation (format <keyword> " ") (text.suffix ..statement_suffix) :abstraction))] + (|>> representation (format <keyword> " ") (text.suffix ..statement_suffix) abstraction))] [throw "throw"] [return "return"] @@ -514,23 +514,23 @@ (def: .public (define name value) (-> Constant Expression Expression) (..apply/2 (..constant "define") - [(|> name :representation ..string) + [(|> name representation ..string) value])) (def: .public (define_function name arguments body!) (-> Constant (List Argument) Statement Statement) - (:abstraction - (format "function " (:representation name) + (abstraction + (format "function " (representation name) (..parameters arguments) " " - (..block (:representation body!))))) + (..block (representation body!))))) (template [<name> <keyword>] [(def: .public <name> Statement (|> <keyword> (text.suffix ..statement_suffix) - :abstraction))] + abstraction))] [break "break"] [continue "continue"] @@ -538,7 +538,7 @@ (def: .public splat (-> Expression Expression) - (|>> :representation (format "...") :abstraction)) + (|>> representation (format "...") abstraction)) ) (def: .public (cond clauses else!) diff --git a/stdlib/source/library/lux/target/python.lux b/stdlib/source/library/lux/target/python.lux index 1b5ecd2ee..0e4e279cb 100644 --- a/stdlib/source/library/lux/target/python.lux +++ b/stdlib/source/library/lux/target/python.lux @@ -1,6 +1,6 @@ (.using [library - [lux {"-" Location Code not or and list if int comment exec try the} + [lux {"-" Location Code not or and list if int comment exec try the is} ["@" target] ["[0]" ffi] [abstract @@ -25,7 +25,7 @@ ["n" nat] ["f" frac]]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) (def: input_separator ", ") @@ -51,9 +51,9 @@ (-> Text Text) (.let [nested_new_line (format text.new_line text.tab)] (for @.old (|>> (format \n+) - (:as java/lang/String) - (java/lang/String::replace (:as java/lang/CharSequence text.new_line) - (:as java/lang/CharSequence nested_new_line))) + (as java/lang/String) + (java/lang/String::replace (as java/lang/CharSequence text.new_line) + (as java/lang/CharSequence nested_new_line))) (|>> (format \n+) (text.replaced text.new_line nested_new_line))))) @@ -64,21 +64,21 @@ (All (_ brand) (Equivalence (Code brand))) (def: (= reference subject) - (# text.equivalence = (:representation reference) (:representation subject)))) + (# text.equivalence = (representation reference) (representation subject)))) (implementation: .public hash (All (_ brand) (Hash (Code brand))) (def: &equivalence ..equivalence) - (def: hash (|>> :representation (# text.hash hash)))) + (def: hash (|>> representation (# text.hash hash)))) (def: .public manual (-> Text Code) - (|>> :abstraction)) + (|>> abstraction)) (def: .public code (-> (Code Any) Text) - (|>> :representation)) + (|>> representation)) (template [<type> <super>] [(with_expansions [<brand> (template.symbol [<type> "'"])] @@ -115,12 +115,12 @@ (def: .public var (-> Text SVar) - (|>> :abstraction)) + (|>> abstraction)) (template [<name> <brand> <prefix>] [(def: .public <name> (-> SVar (Var <brand>)) - (|>> :representation (format <prefix>) :abstraction))] + (|>> representation (format <prefix>) abstraction))] [poly Poly "*"] [keyword Keyword "**"] @@ -128,22 +128,22 @@ (def: .public none Literal - (:abstraction "None")) + (abstraction "None")) (def: .public bool (-> Bit Literal) (|>> (pipe.case #0 "False" #1 "True") - :abstraction)) + abstraction)) (def: .public int (-> Int Literal) - (|>> %.int :abstraction)) + (|>> %.int abstraction)) (def: .public (long value) (-> Int Literal) - (:abstraction (format (%.int value) "L"))) + (abstraction (format (%.int value) "L"))) (def: .public float (-> Frac Literal) @@ -158,7 +158,7 @@ ... else [%.frac]) - :abstraction))) + abstraction))) (def: safe (-> Text Text) @@ -181,21 +181,21 @@ (-> Text Literal) (|>> ..safe (text.enclosed [text.double_quote text.double_quote]) - :abstraction)) + abstraction)) (def: .public unicode (-> Text Literal) (|>> ..string - :representation + representation (format "u") - :abstraction)) + abstraction)) (def: (composite_literal left_delimiter right_delimiter entry_serializer) (All (_ a) (-> Text Text (-> a Text) (-> (List a) Literal))) (function (_ entries) - (<| :abstraction + (<| abstraction ... ..expression (format left_delimiter (|> entries @@ -214,25 +214,25 @@ (def: .public (slice from to list) (-> (Expression Any) (Expression Any) (Expression Any) Access) - (<| :abstraction + (<| abstraction ... ..expression - (format (:representation list) "[" (:representation from) ":" (:representation to) "]"))) + (format (representation list) "[" (representation from) ":" (representation to) "]"))) (def: .public (slice_from from list) (-> (Expression Any) (Expression Any) Access) - (<| :abstraction + (<| abstraction ... ..expression - (format (:representation list) "[" (:representation from) ":]"))) + (format (representation list) "[" (representation from) ":]"))) (def: .public dict (-> (List [(Expression Any) (Expression Any)]) (Computation Any)) - (composite_literal "{" "}" (.function (_ [k v]) (format (:representation k) " : " (:representation v))))) + (composite_literal "{" "}" (.function (_ [k v]) (format (representation k) " : " (representation v))))) (def: .public (apply/* args func) (-> (List (Expression Any)) (Expression Any) (Computation Any)) - (<| :abstraction + (<| abstraction ... ..expression - (format (:representation func) + (format (representation func) "(" (|> args (list#each ..code) (text.interposed ..input_separator)) ")"))) @@ -240,9 +240,9 @@ (template [<name> <brand> <prefix>] [(def: .public <name> (-> (Expression Any) (Expression Any)) - (|>> :representation + (|>> representation (format <prefix>) - :abstraction))] + abstraction))] [splat_poly Poly "*"] [splat_keyword Keyword "**"] @@ -250,7 +250,7 @@ (def: .public (the name object) (-> Text (Expression Any) Access) - (:abstraction (format (:representation object) "." name))) + (abstraction (format (representation object) "." name))) (def: .public (do method args object) (-> Text (List (Expression Any)) (Expression Any) (Computation Any)) @@ -260,20 +260,20 @@ (def: .public (item idx array) (-> (Expression Any) (Expression Any) Access) - (:abstraction (format (:representation array) "[" (:representation idx) "]"))) + (abstraction (format (representation array) "[" (representation idx) "]"))) (def: .public (? test then else) (-> (Expression Any) (Expression Any) (Expression Any) (Computation Any)) - (<| :abstraction + (<| abstraction ..expression - (format (:representation then) " if " (:representation test) " else " (:representation else)))) + (format (representation then) " if " (representation test) " else " (representation else)))) (template [<name> <op>] [(def: .public (<name> param subject) (-> (Expression Any) (Expression Any) (Computation Any)) - (<| :abstraction + (<| abstraction ..expression - (format (:representation subject) " " <op> " " (:representation param))))] + (format (representation subject) " " <op> " " (representation param))))] [is "is"] [= "=="] @@ -303,9 +303,9 @@ (template [<name> <unary>] [(def: .public (<name> subject) (-> (Expression Any) (Computation Any)) - (<| :abstraction + (<| abstraction ... ..expression - (format <unary> " " (:representation subject))))] + (format <unary> " " (representation subject))))] [not "not"] [opposite "-"] @@ -313,53 +313,53 @@ (def: .public (lambda arguments body) (-> (List (Var Any)) (Expression Any) (Computation Any)) - (<| :abstraction + (<| abstraction ..expression (format "lambda " (|> arguments (list#each ..code) (text.interposed ..input_separator)) - ": " (:representation body)))) + ": " (representation body)))) (def: .public (set vars value) (-> (List (Location Any)) (Expression Any) (Statement Any)) - (:abstraction + (abstraction (format (|> vars (list#each ..code) (text.interposed ..input_separator)) " = " - (:representation value)))) + (representation value)))) (def: .public multi (-> (List (Expression Any)) (Expression Any)) (|>> (list#each ..code) (text.interposed ..input_separator) - :abstraction)) + abstraction)) (def: .public (delete where) (-> (Location Any) (Statement Any)) - (:abstraction (format "del " (:representation where)))) + (abstraction (format "del " (representation where)))) (def: .public (if test then! else!) (-> (Expression Any) (Statement Any) (Statement Any) (Statement Any)) - (:abstraction - (format "if " (:representation test) ":" - (..nested (:representation then!)) + (abstraction + (format "if " (representation test) ":" + (..nested (representation then!)) \n+ "else:" - (..nested (:representation else!))))) + (..nested (representation else!))))) (def: .public (when test then!) (-> (Expression Any) (Statement Any) (Statement Any)) - (:abstraction - (format "if " (:representation test) ":" - (..nested (:representation then!))))) + (abstraction + (format "if " (representation test) ":" + (..nested (representation then!))))) (def: .public (then pre! post!) (-> (Statement Any) (Statement Any) (Statement Any)) - (:abstraction - (format (:representation pre!) + (abstraction + (format (representation pre!) \n+ - (:representation post!)))) + (representation post!)))) (template [<keyword> <0>] [(def: .public <0> (Statement Any) - (:abstraction <keyword>))] + (abstraction <keyword>))] ["break" break] ["continue" continue] @@ -367,30 +367,30 @@ (def: .public (while test body! else!) (-> (Expression Any) (Statement Any) (Maybe (Statement Any)) Loop) - (:abstraction - (format "while " (:representation test) ":" - (..nested (:representation body!)) + (abstraction + (format "while " (representation test) ":" + (..nested (representation body!)) (case else! {.#Some else!} (format \n+ "else:" - (..nested (:representation else!))) + (..nested (representation else!))) {.#None} "")))) (def: .public (for_in var inputs body!) (-> SVar (Expression Any) (Statement Any) Loop) - (:abstraction - (format "for " (:representation var) " in " (:representation inputs) ":" - (..nested (:representation body!))))) + (abstraction + (format "for " (representation var) " in " (representation inputs) ":" + (..nested (representation body!))))) (def: .public statement (-> (Expression Any) (Statement Any)) - (|>> :transmutation)) + (|>> transmutation)) (def: .public pass (Statement Any) - (:abstraction "pass")) + (abstraction "pass")) (type: .public Except (Record @@ -400,21 +400,21 @@ (def: .public (try body! excepts) (-> (Statement Any) (List Except) (Statement Any)) - (:abstraction + (abstraction (format "try:" - (..nested (:representation body!)) + (..nested (representation body!)) (|> excepts (list#each (function (_ [classes exception catch!]) (format \n+ "except (" (text.interposed ..input_separator classes) - ") as " (:representation exception) ":" - (..nested (:representation catch!))))) + ") as " (representation exception) ":" + (..nested (representation catch!))))) text.together)))) (template [<name> <keyword> <pre>] [(def: .public (<name> value) (-> (Expression Any) (Statement Any)) - (:abstraction - (format <keyword> (<pre> (:representation value)))))] + (abstraction + (format <keyword> (<pre> (representation value)))))] [raise "raise " |>] [return "return " |>] @@ -429,26 +429,26 @@ {.#None} (.list))] - (:abstraction - (format "exec" (:representation (..tuple (list& code extra))))))) + (abstraction + (format "exec" (representation (..tuple (list& code extra))))))) (def: .public (def name args body) (-> SVar (List (Ex (_ k) (Var k))) (Statement Any) (Statement Any)) - (:abstraction - (format "def " (:representation name) + (abstraction + (format "def " (representation name) "(" (|> args (list#each ..code) (text.interposed ..input_separator)) "):" - (..nested (:representation body))))) + (..nested (representation body))))) (def: .public (import module_name) (-> Text (Statement Any)) - (:abstraction (format "import " module_name))) + (abstraction (format "import " module_name))) (def: .public (comment commentary on) (All (_ brand) (-> Text (Code brand) (Code brand))) - (:abstraction (format "# " (text.replaced text.\n "\n" commentary) \n+ - (:representation on)))) + (abstraction (format "# " (text.replaced text.\n "\n" commentary) \n+ + (representation on)))) ) (syntax: (arity_inputs [arity <code>.nat]) diff --git a/stdlib/source/library/lux/target/r.lux b/stdlib/source/library/lux/target/r.lux index ad23a3e20..c4fa1d87a 100644 --- a/stdlib/source/library/lux/target/r.lux +++ b/stdlib/source/library/lux/target/r.lux @@ -20,7 +20,7 @@ [number ["f" frac]]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) (abstract: .public (Code kind) Text @@ -51,23 +51,23 @@ (def: .public var (-> Text SVar) - (|>> :abstraction)) + (|>> abstraction)) (def: .public var_args PVar - (:abstraction "...")) + (abstraction "...")) (def: .public manual (-> Text Code) - (|>> :abstraction)) + (|>> abstraction)) (def: .public code (-> (Code Any) Text) - (|>> :representation)) + (|>> representation)) (def: (self_contained code) (-> Text Expression) - (:abstraction + (abstraction (format "(" code ")"))) ... Added the carriage return for better Windows compatibility. @@ -89,15 +89,15 @@ (def: .public (block expression) (-> Expression Expression) - (:abstraction + (abstraction (format "{" - (..nested (:representation expression)) + (..nested (representation expression)) \n+ "}"))) (template [<name> <r>] [(def: .public <name> Expression - (:abstraction <r>))] + (abstraction <r>))] [null "NULL"] [n/a "NA"] @@ -116,11 +116,11 @@ (|>> (pipe.case #0 "FALSE" #1 "TRUE") - :abstraction)) + abstraction)) (def: .public int (-> Int Expression) - (|>> %.int :abstraction)) + (|>> %.int abstraction)) (def: .public float (-> Frac Expression) @@ -155,27 +155,27 @@ (def: .public string (-> Text Expression) - (|>> ..safe %.text :abstraction)) + (|>> ..safe %.text abstraction)) (def: .public (slice from to list) (-> Expression Expression Expression Expression) (..self_contained - (format (:representation list) - "[" (:representation from) ":" (:representation to) "]"))) + (format (representation list) + "[" (representation from) ":" (representation to) "]"))) (def: .public (slice_from from list) (-> Expression Expression Expression) (..self_contained - (format (:representation list) - "[-1" ":-" (:representation from) "]"))) + (format (representation list) + "[-1" ":-" (representation from) "]"))) (def: .public (apply args func) (-> (List Expression) Expression Expression) - (let [func (:representation func) + (let [func (representation func) spacing (|> " " (list.repeated (text.size func)) text.together)] - (:abstraction + (abstraction (format func "(" (|> args (list#each ..code) @@ -195,17 +195,17 @@ (def: .public named_list (-> (List [Text Expression]) Expression) (|>> (list#each (.function (_ [key value]) - (:abstraction (format key "=" (:representation value))))) + (abstraction (format key "=" (representation value))))) ..list)) (def: .public (apply_kw args kw_args func) (-> (List Expression) (List [Text Expression]) Expression Expression) (..self_contained - (format (:representation func) + (format (representation func) (format "(" (text.interposed "," (list#each ..code args)) "," (text.interposed "," (list#each (.function (_ [key val]) - (format key "=" (:representation val))) + (format key "=" (representation val))) kw_args)) ")")))) @@ -250,20 +250,20 @@ (def: .public (item idx list) (-> Expression Expression Expression) (..self_contained - (format (:representation list) "[[" (:representation idx) "]]"))) + (format (representation list) "[[" (representation idx) "]]"))) (def: .public (if test then else) (-> Expression Expression Expression Expression) - (:abstraction - (format "if(" (:representation test) ")" - " " (.._block (:representation then)) - " else " (.._block (:representation else))))) + (abstraction + (format "if(" (representation test) ")" + " " (.._block (representation then)) + " else " (.._block (representation else))))) (def: .public (when test then) (-> Expression Expression Expression) - (:abstraction - (format "if(" (:representation test) ") {" - (.._block (:representation then)) + (abstraction + (format "if(" (representation test) ") {" + (.._block (representation then)) \n+ "}"))) (def: .public (cond clauses else) @@ -277,9 +277,9 @@ [(def: .public (<name> param subject) (-> Expression Expression Expression) (..self_contained - (format (:representation subject) + (format (representation subject) " " <op> " " - (:representation param))))] + (representation param))))] [= "=="] [< "<"] @@ -315,7 +315,7 @@ (template [<name> <op>] [(def: .public <name> (-> Expression Expression) - (|>> :representation (format <op>) ..self_contained))] + (|>> representation (format <op>) ..self_contained))] [not "!"] [negate "-"] @@ -328,25 +328,25 @@ (def: .public (range from to) (-> Expression Expression Expression) (..self_contained - (format (:representation from) ":" (:representation to)))) + (format (representation from) ":" (representation to)))) (def: .public (function inputs body) (-> (List (Ex (_ k) (Var k))) Expression Expression) (let [args (|> inputs (list#each ..code) (text.interposed ", "))] (..self_contained (format "function(" args ") " - (.._block (:representation body)))))) + (.._block (representation body)))))) (def: .public (try body warning error finally) (-> Expression (Maybe Expression) (Maybe Expression) (Maybe Expression) Expression) - (let [optional (: (-> Text (Maybe Expression) (-> Text Text) Text) - (.function (_ parameter value preparation) - (|> value - (maybe#each (|>> :representation preparation (format ", " parameter " = "))) - (maybe.else ""))))] + (let [optional (is (-> Text (Maybe Expression) (-> Text Text) Text) + (.function (_ parameter value preparation) + (|> value + (maybe#each (|>> representation preparation (format ", " parameter " = "))) + (maybe.else ""))))] (..self_contained (format "tryCatch(" - (.._block (:representation body)) + (.._block (representation body)) (optional "warning" warning function.identity) (optional "error" error function.identity) (optional "finally" finally .._block) @@ -355,14 +355,14 @@ (def: .public (while test body) (-> Expression Expression Expression) (..self_contained - (format "while (" (:representation test) ") " - (.._block (:representation body))))) + (format "while (" (representation test) ") " + (.._block (representation body))))) (def: .public (for_in var inputs body) (-> SVar Expression Expression Expression) (..self_contained - (format "for (" (:representation var) " in " (:representation inputs) ")" - (.._block (:representation body))))) + (format "for (" (representation var) " in " (representation inputs) ")" + (.._block (representation body))))) (template [<name> <keyword>] [(def: .public (<name> message) @@ -376,17 +376,17 @@ (def: .public (set! var value) (-> SVar Expression Expression) (..self_contained - (format (:representation var) " <- " (:representation value)))) + (format (representation var) " <- " (representation value)))) (def: .public (set_item! idx value list) (-> Expression Expression SVar Expression) (..self_contained - (format (:representation list) "[[" (:representation idx) "]] <- " (:representation value)))) + (format (representation list) "[[" (representation idx) "]] <- " (representation value)))) (def: .public (then pre post) (-> Expression Expression Expression) - (:abstraction - (format (:representation pre) + (abstraction + (format (representation pre) \n+ - (:representation post)))) + (representation post)))) ) diff --git a/stdlib/source/library/lux/target/ruby.lux b/stdlib/source/library/lux/target/ruby.lux index a5949aab0..a89537de1 100644 --- a/stdlib/source/library/lux/target/ruby.lux +++ b/stdlib/source/library/lux/target/ruby.lux @@ -24,7 +24,7 @@ ["n" nat] ["f" frac]]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) (def: input_separator ", ") (def: statement_suffix ";") @@ -47,15 +47,15 @@ (All (_ brand) (Equivalence (Code brand))) (def: (= reference subject) - (# text.equivalence = (:representation reference) (:representation subject)))) + (# text.equivalence = (representation reference) (representation subject)))) (def: .public manual (-> Text Code) - (|>> :abstraction)) + (|>> abstraction)) (def: .public code (-> (Code Any) Text) - (|>> :representation)) + (|>> representation)) (template [<type> <super>+] [(with_expansions [<brand> (template.symbol [<type> "'"])] @@ -88,7 +88,7 @@ (template [<var> <prefix> <constructor>] [(def: .public <constructor> (-> Text <var>) - (|>> (format <prefix>) :abstraction))] + (|>> (format <prefix>) abstraction))] [LVar "l_" local] [CVar "C_" constant] @@ -101,7 +101,7 @@ [(template [<name> <input> <output>] [(def: .public <name> (-> <input> <output>) - (|>> :representation (format <prefix>) :abstraction))] + (|>> representation (format <prefix>) abstraction))] [<modifier> LVar <var>] [<unpacker> Expression Computation] @@ -145,18 +145,18 @@ (-> (List Expression) Expression) (|>> (list#each ..code) (text.interposed ..input_separator) - :abstraction)) + abstraction)) (def: .public nil Literal - (:abstraction "nil")) + (abstraction "nil")) (def: .public bool (-> Bit Literal) (|>> (pipe.case #0 "false" #1 "true") - :abstraction)) + abstraction)) (def: safe (-> Text Text) @@ -178,7 +178,7 @@ (template [<format> <name> <type> <prep>] [(def: .public <name> (-> <type> Literal) - (|>> <prep> <format> :abstraction))] + (|>> <prep> <format> abstraction))] [%.int int Int (<|)] [%.text string Text ..safe] @@ -198,29 +198,29 @@ ... else [%.frac]) - :abstraction)) + abstraction)) (def: .public (array_range from to array) (-> Expression Expression Expression Computation) - (|> (format (:representation from) ".." (:representation to)) + (|> (format (representation from) ".." (representation to)) (text.enclosed ["[" "]"]) - (format (:representation array)) - :abstraction)) + (format (representation array)) + abstraction)) (def: .public array (-> (List Expression) Computation) - (|>> (list#each (|>> :representation (text.suffix ..input_separator))) + (|>> (list#each (|>> representation (text.suffix ..input_separator))) text.together (text.enclosed ["[" "]"]) - :abstraction)) + abstraction)) (def: .public hash (-> (List [Expression Expression]) Computation) (|>> (list#each (.function (_ [k v]) - (format (:representation k) " => " (:representation v) ..input_separator))) + (format (representation k) " => " (representation v) ..input_separator))) text.together (text.enclosed ["{" "}"]) - :abstraction)) + abstraction)) (def: (control_structure content) (-> Text Text) @@ -235,16 +235,16 @@ (def: (block it) (-> Block Text) (|> (format (|> (.the #parameters it) - (list#each (|>> :representation)) + (list#each (|>> representation)) (text.interposed ..input_separator) (text.enclosed' "|")) - (..nested (:representation (.the #body it)))) + (..nested (representation (.the #body it)))) (text.enclosed ["{" "}"]))) (def: .public (apply/* arguments block func) (-> (List Expression) (Maybe Block) Expression Computation) (let [arguments (|> arguments - (list#each (|>> :representation)) + (list#each (|>> representation)) (text.interposed ..input_separator) (text.enclosed ["(" ")"])) block (case block @@ -253,72 +253,72 @@ {.#Some [inputs block]} (|> block - :representation + representation nested control_structure (format " do " (|> inputs - (list#each (|>> :representation)) + (list#each (|>> representation)) (text.interposed ..input_separator) (text.enclosed' "|")))))] - (:abstraction (format (:representation func) arguments block)))) + (abstraction (format (representation func) arguments block)))) (def: .public (the field object) (-> Text Expression Access) - (:abstraction (format (:representation object) "." field))) + (abstraction (format (representation object) "." field))) (def: .public (item idx array) (-> Expression Expression Access) - (|> (:representation idx) + (|> (representation idx) (text.enclosed ["[" "]"]) - (format (:representation array)) - :abstraction)) + (format (representation array)) + abstraction)) (def: .public (? test then else) (-> Expression Expression Expression Computation) - (|> (format (:representation test) " ? " - (:representation then) " : " - (:representation else)) + (|> (format (representation test) " ? " + (representation then) " : " + (representation else)) (text.enclosed ["(" ")"]) - :abstraction)) + abstraction)) (def: .public statement (-> Expression Statement) - (|>> :representation + (|>> representation (text.suffix ..statement_suffix) - :abstraction)) + abstraction)) (def: .public (then pre! post!) (-> Statement Statement Statement) - (:abstraction - (format (:representation pre!) + (abstraction + (format (representation pre!) \n+ - (:representation post!)))) + (representation post!)))) (def: .public (set vars value) (-> (List Location) Expression Statement) - (:abstraction + (abstraction (format (|> vars - (list#each (|>> :representation)) + (list#each (|>> representation)) (text.interposed ..input_separator)) - " = " (:representation value) ..statement_suffix))) + " = " (representation value) ..statement_suffix))) (def: .public (if test then! else!) (-> Expression Statement Statement Statement) - (<| :abstraction + (<| abstraction ..control_structure - (format "if " (:representation test) - (..nested (:representation then!)) + (format "if " (representation test) + (..nested (representation then!)) \n+ "else" - (..nested (:representation else!))))) + (..nested (representation else!))))) (template [<name> <control_structure>] [(def: .public (<name> test then!) (-> Expression Statement Statement) - (<| :abstraction + (<| abstraction ..control_structure - (format <control_structure> " " (:representation test) - (..nested (:representation then!)))))] + (format <control_structure> " " (representation test) + (..nested (representation then!)))))] [when "if"] [while "while"] @@ -326,12 +326,12 @@ (def: .public (for_in var array iteration!) (-> LVar Expression Statement Statement) - (<| :abstraction + (<| abstraction ..control_structure - (format "for " (:representation var) - " in " (:representation array) + (format "for " (representation var) + " in " (representation array) " do " - (..nested (:representation iteration!))))) + (..nested (representation iteration!))))) (type: .public Rescue (Record @@ -341,36 +341,36 @@ (def: .public (begin body! rescues) (-> Statement (List Rescue) Statement) - (<| :abstraction + (<| abstraction ..control_structure - (format "begin" (..nested (:representation body!)) + (format "begin" (..nested (representation body!)) (|> rescues (list#each (.function (_ [classes exception rescue]) (format \n+ "rescue " (text.interposed ..input_separator classes) - " => " (:representation exception) - (..nested (:representation rescue))))) + " => " (representation exception) + (..nested (representation rescue))))) (text.interposed \n+))))) (def: .public (catch expectation block) (-> Expression Block Expression) - (<| :abstraction - (format "catch(" (:representation expectation) ") " + (<| abstraction + (format "catch(" (representation expectation) ") " (..block block)))) (def: .public (return value) (-> Expression Statement) - (:abstraction (format "return " (:representation value) ..statement_suffix))) + (abstraction (format "return " (representation value) ..statement_suffix))) (def: .public (raise message) (-> Expression Expression) - (:abstraction (format "raise " (:representation message)))) + (abstraction (format "raise " (representation message)))) (template [<name> <keyword>] [(def: .public <name> Statement (|> <keyword> (text.suffix ..statement_suffix) - :abstraction))] + abstraction))] [next "next"] [redo "redo"] @@ -383,14 +383,14 @@ (def: .public (function name args body!) (-> LVar (List LVar) Statement Statement) - (<| :abstraction + (<| abstraction ..control_structure - (format "def " (:representation name) + (format "def " (representation name) (|> args - (list#each (|>> :representation)) + (list#each (|>> representation)) (text.interposed ..input_separator) (text.enclosed ["(" ")"])) - (..nested (:representation body!))))) + (..nested (representation body!))))) (def: .public (lambda name block) (-> (Maybe LVar) Block Literal) @@ -400,14 +400,14 @@ proc {.#Some name} - (format (:representation name) " = " proc)) + (format (representation name) " = " proc)) (text.enclosed ["(" ")"]) - :abstraction))) + abstraction))) (template [<op> <name>] [(def: .public (<name> parameter subject) (-> Expression Expression Computation) - (:abstraction (format "(" (:representation subject) " " <op> " " (:representation parameter) ")")))] + (abstraction (format "(" (representation subject) " " <op> " " (representation parameter) ")")))] ["==" =] [ "<" <] @@ -435,7 +435,7 @@ (template [<unary> <name>] [(def: .public (<name> subject) (-> Expression Computation) - (:abstraction (format "(" <unary> (:representation subject) ")")))] + (abstraction (format "(" <unary> (representation subject) ")")))] ["!" not] ["~" bit_not] @@ -444,8 +444,8 @@ (def: .public (comment commentary on) (All (_ brand) (-> Text (Code brand) (Code brand))) - (:abstraction (format "# " (..safe commentary) \n+ - (:representation on)))) + (abstraction (format "# " (..safe commentary) \n+ + (representation on)))) (template [<name>] [(`` (def: .public ((~~ (template.symbol [<name> "/*"])) attributes) diff --git a/stdlib/source/library/lux/target/scheme.lux b/stdlib/source/library/lux/target/scheme.lux index 2ea9a66e8..3bd2b22ce 100644 --- a/stdlib/source/library/lux/target/scheme.lux +++ b/stdlib/source/library/lux/target/scheme.lux @@ -19,7 +19,7 @@ ["n" nat] ["f" frac]]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) ... Added the carriage return for better Windows compatibility. (def: \n+ @@ -38,13 +38,13 @@ (All (_ brand) (Equivalence (Code brand))) (def: (= reference subject) - (# text.equivalence = (:representation reference) (:representation subject)))) + (# text.equivalence = (representation reference) (representation subject)))) (implementation: .public hash (All (_ brand) (Hash (Code brand))) (def: &equivalence ..equivalence) - (def: hash (|>> :representation (# text.hash hash)))) + (def: hash (|>> representation (# text.hash hash)))) (template [<type> <brand> <super>+] [(abstract: .public (<brand> brand) Any) @@ -68,15 +68,15 @@ (def: .public manual (-> Text Code) - (|>> :abstraction)) + (|>> abstraction)) (def: .public code (-> (Code Any) Text) - (|>> :representation)) + (|>> representation)) (def: .public var (-> Text Var) - (|>> :abstraction)) + (|>> abstraction)) (def: (arguments [mandatory rest]) (-> Arguments (Code Any)) @@ -87,34 +87,34 @@ rest _ - (|> (format " . " (:representation rest)) + (|> (format " . " (representation rest)) (format (|> mandatory (list#each ..code) (text.interposed " "))) (text.enclosed ["(" ")"]) - :abstraction)) + abstraction)) {.#None} (|> mandatory (list#each ..code) (text.interposed " ") (text.enclosed ["(" ")"]) - :abstraction))) + abstraction))) (def: .public nil Computation - (:abstraction "'()")) + (abstraction "'()")) (def: .public bool (-> Bit Computation) (|>> (pipe.case #0 "#f" #1 "#t") - :abstraction)) + abstraction)) (def: .public int (-> Int Computation) - (|>> %.int :abstraction)) + (|>> %.int abstraction)) (def: .public float (-> Frac Computation) @@ -129,7 +129,7 @@ ... else [%.frac]) - :abstraction)) + abstraction)) (def: .public positive_infinity Computation (..float f.positive_infinity)) (def: .public negative_infinity Computation (..float f.negative_infinity)) @@ -153,26 +153,26 @@ (def: .public string (-> Text Computation) - (|>> ..safe %.text :abstraction)) + (|>> ..safe %.text abstraction)) (def: .public symbol (-> Text Computation) - (|>> (format "'") :abstraction)) + (|>> (format "'") abstraction)) (def: form (-> (List (Code Any)) Code) (.let [nested_new_line (format \n+ text.tab)] (|>> (pipe.case {.#End} - (:abstraction "()") + (abstraction "()") {.#Item head tail} (|> tail - (list#each (|>> :representation ..nested)) - {.#Item (:representation head)} + (list#each (|>> representation ..nested)) + {.#Item (representation head)} (text.interposed nested_new_line) (text.enclosed ["(" ")"]) - :abstraction))))) + abstraction))))) (def: .public (apply/* args func) (-> (List Expression) Expression Computation) diff --git a/stdlib/source/library/lux/test.lux b/stdlib/source/library/lux/test.lux index b4dea2627..09b549d09 100644 --- a/stdlib/source/library/lux/test.lux +++ b/stdlib/source/library/lux/test.lux @@ -85,9 +85,9 @@ (def: .public (and' left right) (-> Assertion Assertion Assertion) - (let [[read! write!] (: [(Async [Tally Text]) - (async.Resolver [Tally Text])] - (async.async [])) + (let [[read! write!] (is [(Async [Tally Text]) + (async.Resolver [Tally Text])] + (async.async [])) _ (|> left (async.upon! (function (_ [l_tally l_documentation]) (async.upon! (function (_ [r_tally r_documentation]) @@ -193,10 +193,10 @@ (the #expected_coverage tally)) unexpected (set.difference (the #expected_coverage tally) (the #actual_coverage tally)) - report (: (-> (Set Symbol) Text) - (|>> set.list - (list.sorted (# symbol.order <)) - (exception.listing %.symbol))) + report (is (-> (Set Symbol) Text) + (|>> set.list + (list.sorted (# symbol.order <)) + (exception.listing %.symbol))) expected_definitions_to_cover (set.size (the #expected_coverage tally)) unexpected_definitions_covered (set.size unexpected) actual_definitions_covered (n.- unexpected_definitions_covered @@ -339,8 +339,8 @@ (` ((~! ..reference) (~ definition)))) coverage)] (in (list (` ((~! <function>) - (: (.List .Symbol) - (.list (~+ coverage))) + (is (.List .Symbol) + (.list (~+ coverage))) (~ condition)))))))] [cover' ..|cover'|] @@ -353,8 +353,8 @@ (` ((~! ..reference) (~ definition)))) coverage)] (in (list (` ((~! ..|for|) - (: (.List .Symbol) - (.list (~+ coverage))) + (is (.List .Symbol) + (.list (~+ coverage))) (~ test))))))) (def: (covering' module coverage test) @@ -398,22 +398,22 @@ (do random.monad [seed random.nat .let [prng (random.pcg_32 [..pcg_32_magic_inc seed]) - run! (: (-> Test Assertion) - (|>> (random.result prng) - product.right - (function (_ _)) - "lux try" - (pipe.case - {try.#Success output} - output - - {try.#Failure error} - (..assertion (exception.error ..error_during_execution [error]) false)))) - state (: (Atom (Dictionary Nat [Tally Text])) - (atom.atom (dictionary.empty n.order))) - [read! write!] (: [Assertion - (async.Resolver [Tally Text])] - (async.async [])) + run! (is (-> Test Assertion) + (|>> (random.result prng) + product.right + (function (_ _)) + "lux try" + (pipe.case + {try.#Success output} + output + + {try.#Failure error} + (..assertion (exception.error ..error_during_execution [error]) false)))) + state (is (Atom (Dictionary Nat [Tally Text])) + (atom.atom (dictionary.empty n.order))) + [read! write!] (is [Assertion + (async.Resolver [Tally Text])] + (async.async [])) _ (list#mix (function (_ test index) (exec (|> (run! test) diff --git a/stdlib/source/library/lux/time.lux b/stdlib/source/library/lux/time.lux index 425c1300b..b0bf5c94c 100644 --- a/stdlib/source/library/lux/time.lux +++ b/stdlib/source/library/lux/time.lux @@ -19,7 +19,7 @@ [number ["n" nat ("[1]#[0]" decimal)]]] [type - abstract]]] + [abstract {"-" pattern}]]]] [/ ["[0]" duration {"+" Duration}]]) @@ -81,23 +81,23 @@ (def: .public midnight Time - (:abstraction 0)) + (abstraction 0)) (def: .public (of_millis milli_seconds) (-> Nat (Try Time)) (if (n.< ..limit milli_seconds) - {try.#Success (:abstraction milli_seconds)} + {try.#Success (abstraction milli_seconds)} (exception.except ..time_exceeds_a_day [milli_seconds]))) (def: .public millis (-> Time Nat) - (|>> :representation)) + (|>> representation)) (implementation: .public equivalence (Equivalence Time) (def: (= param subject) - (n.= (:representation param) (:representation subject)))) + (n.= (representation param) (representation subject)))) (implementation: .public order (Order Time) @@ -105,7 +105,7 @@ (def: &equivalence ..equivalence) (def: (< param subject) - (n.< (:representation param) (:representation subject)))) + (n.< (representation param) (representation subject)))) (`` (implementation: .public enum (Enum Time) @@ -113,20 +113,20 @@ (def: &order ..order) (def: succ - (|>> :representation ++ (n.% ..limit) :abstraction)) + (|>> representation ++ (n.% ..limit) abstraction)) (def: pred - (|>> :representation + (|>> representation (pipe.case 0 ..limit millis millis) -- - :abstraction)))) + abstraction)))) (def: .public parser (Parser Time) - (let [millis (: (-> Duration Nat) - (|>> duration.millis .nat)) + (let [millis (is (-> Duration Nat) + (|>> duration.millis .nat)) hour (millis duration.hour) minute (millis duration.minute) second (millis duration.second) @@ -138,7 +138,7 @@ _ (<text>.this ..separator) utc_second ..second_parser utc_millis ..millis_parser] - (in (:abstraction + (in (abstraction ($_ n.+ (n.* utc_hour hour) (n.* utc_minute minute) diff --git a/stdlib/source/library/lux/time/date.lux b/stdlib/source/library/lux/time/date.lux index 50d190331..c79e12d32 100644 --- a/stdlib/source/library/lux/time/date.lux +++ b/stdlib/source/library/lux/time/date.lux @@ -23,7 +23,7 @@ ["n" nat ("[1]#[0]" decimal)] ["i" int]]] [type - abstract]]] + [abstract {"-" pattern}]]]] ["[0]" // "_" ["[1][0]" year {"+" Year}] ["[1][0]" month {"+" Month}]]) @@ -80,7 +80,7 @@ (if (..invalid_day? year month day_of_month) (exception.except ..invalid_day [year month day_of_month]) {try.#Success - (:abstraction + (abstraction [#year year #month month #day day_of_month])})) @@ -95,7 +95,7 @@ (template [<name> <type> <field>] [(def: .public <name> (-> Date <type>) - (|>> :representation (the <field>)))] + (|>> representation (the <field>)))] [year Year #year] [month Month #month] @@ -106,8 +106,8 @@ (Equivalence Date) (def: (= reference sample) - (let [reference (:representation reference) - sample (:representation sample)] + (let [reference (representation reference) + sample (representation sample)] (and (# //year.equivalence = (the #year reference) (the #year sample)) @@ -123,8 +123,8 @@ (def: &equivalence ..equivalence) (def: (< reference sample) - (let [reference (:representation reference) - sample (:representation sample)] + (let [reference (representation reference) + sample (representation sample)] (or (# //year.order < (the #year reference) (the #year sample)) @@ -277,7 +277,7 @@ (def: (civil_year utc_month utc_year) (-> Nat Year Int) (let [... Coercing, because the year is already in external form. - utc_year (:as Int utc_year)] + utc_year (as Int utc_year)] (if (n.< ..first_month_of_civil_year utc_month) (-- utc_year) utc_year))) @@ -336,7 +336,7 @@ year)] ... Coercing, because the year is already in internal form. (try.trusted - (..date (:as Year year) + (..date (as Year year) (maybe.trusted (dictionary.value month ..month_by_number)) day)))) diff --git a/stdlib/source/library/lux/time/duration.lux b/stdlib/source/library/lux/time/duration.lux index dc2e66fc2..2a2d00771 100644 --- a/stdlib/source/library/lux/time/duration.lux +++ b/stdlib/source/library/lux/time/duration.lux @@ -1,43 +1,43 @@ (.using - [library - [lux "*" - [abstract - [equivalence {"+" Equivalence}] - [order {"+" Order}] - [enum {"+" Enum}] - [codec {"+" Codec}] - [monoid {"+" Monoid}] - [monad {"+" do}]] - [control - ["[0]" try] - ["<>" parser - ["<[0]>" text {"+" Parser}]]] - [data - ["[0]" text ("[1]#[0]" monoid)]] - [math - [number - ["i" int] - ["[0]" nat ("[1]#[0]" decimal)]]] - [type - abstract]]] - ["[0]" // "_" - ["[1][0]" year]]) + [library + [lux "*" + [abstract + [equivalence {"+" Equivalence}] + [order {"+" Order}] + [enum {"+" Enum}] + [codec {"+" Codec}] + [monoid {"+" Monoid}] + [monad {"+" do}]] + [control + ["[0]" try] + ["<>" parser + ["<[0]>" text {"+" Parser}]]] + [data + ["[0]" text ("[1]#[0]" monoid)]] + [math + [number + ["i" int] + ["[0]" nat ("[1]#[0]" decimal)]]] + [type + [abstract {"-" pattern}]]]] + ["[0]" // "_" + ["[1][0]" year]]) (abstract: .public Duration Int (def: .public of_millis (-> Int Duration) - (|>> :abstraction)) + (|>> abstraction)) (def: .public millis (-> Duration Int) - (|>> :representation)) + (|>> representation)) (template [<op> <name>] [(def: .public (<name> param subject) (-> Duration Duration Duration) - (:abstraction (<op> (:representation param) (:representation subject))))] + (abstraction (<op> (representation param) (representation subject))))] [i.+ merged] [i.% framed] @@ -46,7 +46,7 @@ (template [<op> <name>] [(def: .public (<name> scalar) (-> Nat Duration Duration) - (|>> :representation (<op> (.int scalar)) :abstraction))] + (|>> representation (<op> (.int scalar)) abstraction))] [i.* up] [i./ down] @@ -54,29 +54,29 @@ (def: .public inverse (-> Duration Duration) - (|>> :representation (i.* -1) :abstraction)) + (|>> representation (i.* -1) abstraction)) (def: .public (ticks param subject) (-> Duration Duration Int) - (i./ (:representation param) (:representation subject))) + (i./ (representation param) (representation subject))) (implementation: .public equivalence (Equivalence Duration) (def: (= param subject) - (i.= (:representation param) (:representation subject)))) + (i.= (representation param) (representation subject)))) (implementation: .public order (Order Duration) (def: &equivalence ..equivalence) (def: (< param subject) - (i.< (:representation param) (:representation subject)))) + (i.< (representation param) (representation subject)))) (template [<op> <name>] [(def: .public <name> (-> Duration Bit) - (|>> :representation (<op> +0)))] + (|>> representation (<op> +0)))] [i.> positive?] [i.< negative?] @@ -154,15 +154,15 @@ (def: parser (Parser Duration) - (let [section (: (-> Text Text (Parser Nat)) - (function (_ suffix false_suffix) - (|> (<text>.many <text>.decimal) - (<>.codec nat.decimal) - (<>.before (case false_suffix - "" (<text>.this suffix) - _ (<>.after (<>.not (<text>.this false_suffix)) - (<text>.this suffix)))) - (<>.else 0))))] + (let [section (is (-> Text Text (Parser Nat)) + (function (_ suffix false_suffix) + (|> (<text>.many <text>.decimal) + (<>.codec nat.decimal) + (<>.before (case false_suffix + "" (<text>.this suffix) + _ (<>.after (<>.not (<text>.this false_suffix)) + (<text>.this suffix)))) + (<>.else 0))))] (do <>.monad [sign (<>.or (<text>.this ..negative_sign) (<text>.this ..positive_sign)) diff --git a/stdlib/source/library/lux/time/instant.lux b/stdlib/source/library/lux/time/instant.lux index c83d994e4..b48836c7e 100644 --- a/stdlib/source/library/lux/time/instant.lux +++ b/stdlib/source/library/lux/time/instant.lux @@ -22,7 +22,7 @@ ["i" int] ["f" frac]]] [type - abstract]]] + [abstract {"-" pattern}]]]] ["[0]" // {"+" Time} ["[0]" duration {"+" Duration}] ["[0]" year {"+" Year}] @@ -35,40 +35,40 @@ (def: .public of_millis (-> Int Instant) - (|>> :abstraction)) + (|>> abstraction)) (def: .public millis (-> Instant Int) - (|>> :representation)) + (|>> representation)) (def: .public (span from to) (-> Instant Instant Duration) - (duration.of_millis (i.- (:representation from) (:representation to)))) + (duration.of_millis (i.- (representation from) (representation to)))) (def: .public (after duration instant) (-> Duration Instant Instant) - (:abstraction (i.+ (duration.millis duration) (:representation instant)))) + (abstraction (i.+ (duration.millis duration) (representation instant)))) (def: .public (relative instant) (-> Instant Duration) - (|> instant :representation duration.of_millis)) + (|> instant representation duration.of_millis)) (def: .public (absolute offset) (-> Duration Instant) - (|> offset duration.millis :abstraction)) + (|> offset duration.millis abstraction)) (implementation: .public equivalence (Equivalence Instant) (def: (= param subject) - (# i.equivalence = (:representation param) (:representation subject)))) + (# i.equivalence = (representation param) (representation subject)))) (implementation: .public order (Order Instant) (def: &equivalence ..equivalence) (def: (< param subject) - (# i.order < (:representation param) (:representation subject)))) + (# i.order < (representation param) (representation subject)))) (`` (implementation: .public enum (Enum Instant) @@ -76,7 +76,7 @@ (def: &order ..order) (~~ (template [<name>] [(def: <name> - (|>> :representation (# i.enum <name>) :abstraction))] + (|>> representation (# i.enum <name>) abstraction))] [succ] [pred] )))) @@ -153,38 +153,38 @@ (io (..of_millis (for @.old ("jvm invokestatic:java.lang.System:currentTimeMillis:") @.jvm (|> ("jvm member invoke static" [] "java.lang.System" "currentTimeMillis" []) ("jvm object cast") - (: (Primitive "java.lang.Long")) - (:as Int)) + (is (Primitive "java.lang.Long")) + (as Int)) @.js (let [date ("js object new" ("js constant" "Date") [])] (|> ("js object do" "getTime" date []) - (:as Frac) + (as Frac) "lux f64 i64")) @.python (let [time ("python import" "time")] (|> ("python object do" "time" time []) - (:as Frac) + (as Frac) (f.* +1,000.0) "lux f64 i64")) @.lua (|> ("lua apply" ("lua constant" "os.time") []) - (:as Int) + (as Int) (i.* +1,000)) @.ruby (let [% ("ruby constant" "Time") % ("ruby object do" "now" % [])] (|> ("ruby object do" "to_f" % []) - (:as Frac) + (as Frac) (f.* +1,000.0) "lux f64 i64")) @.php (|> ("php constant" "time") "php apply" - (:as Int) + (as Int) (i.* +1,000)) @.scheme (|> ("scheme constant" "current-second") - (:as Int) + (as Int) (i.* +1,000) ("scheme apply" ("scheme constant" "exact")) ("scheme apply" ("scheme constant" "truncate"))) @.common_lisp (|> ("common_lisp constant" "get-universal-time") "common_lisp apply" - (:as Int) + (as Int) (i.* +1,000)) )))) diff --git a/stdlib/source/library/lux/time/year.lux b/stdlib/source/library/lux/time/year.lux index 09ad9e42d..26924080e 100644 --- a/stdlib/source/library/lux/time/year.lux +++ b/stdlib/source/library/lux/time/year.lux @@ -1,24 +1,24 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}] - [codec {"+" Codec}] - [equivalence {"+" Equivalence}] - [order {"+" Order}]] - [control - ["[0]" try {"+" Try}] - ["[0]" exception {"+" exception:}] - ["<>" parser - ["<[0]>" text {"+" Parser}]]] - [data - ["[0]" text ("[1]#[0]" monoid)]] - [math - [number - ["n" nat ("[1]#[0]" decimal)] - ["i" int ("[1]#[0]" decimal)]]] - [type - abstract]]]) + [library + [lux "*" + [abstract + [monad {"+" do}] + [codec {"+" Codec}] + [equivalence {"+" Equivalence}] + [order {"+" Order}]] + [control + ["[0]" try {"+" Try}] + ["[0]" exception {"+" exception:}] + ["<>" parser + ["<[0]>" text {"+" Parser}]]] + [data + ["[0]" text ("[1]#[0]" monoid)]] + [math + [number + ["n" nat ("[1]#[0]" decimal)] + ["i" int ("[1]#[0]" decimal)]]] + [type + [abstract {"-" pattern}]]]]) (def: (internal year) (-> Int Int) @@ -42,15 +42,15 @@ (-> Int (Try Year)) (case value +0 (exception.except ..there_is_no_year_0 []) - _ {try.#Success (:abstraction (..internal value))})) + _ {try.#Success (abstraction (..internal value))})) (def: .public value (-> Year Int) - (|>> :representation ..external)) + (|>> representation ..external)) (def: .public epoch Year - (:abstraction +1970)) + (abstraction +1970)) ) (def: .public days diff --git a/stdlib/source/library/lux/tool/compiler/default/init.lux b/stdlib/source/library/lux/tool/compiler/default/init.lux index 48a1fb475..9f615c86e 100644 --- a/stdlib/source/library/lux/tool/compiler/default/init.lux +++ b/stdlib/source/library/lux/tool/compiler/default/init.lux @@ -146,7 +146,7 @@ (do ///phase.monad [_ (///directive.lifted_analysis (moduleA.set_compiled module)) - analysis_module (<| (: (Operation .Module)) + analysis_module (<| (is (Operation .Module)) ///directive.lifted_analysis extension.lifted meta.current_module) @@ -276,7 +276,7 @@ ///.#process (function (_ state archive) (again (<| (///phase.result' state) (do [! ///phase.monad] - [analysis_module (<| (: (Operation .Module)) + [analysis_module (<| (is (Operation .Module)) ///directive.lifted_analysis extension.lifted meta.current_module) diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux index b4c2a8be8..0a69b7995 100644 --- a/stdlib/source/library/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux @@ -29,7 +29,7 @@ ["_" binary {"+" Writer}]]] ["[0]" meta ["[0]" configuration {"+" Configuration}]] - [type {"+" :sharing} + [type {"+" sharing} ["[0]" check]] [world ["[0]" file {"+" Path}] @@ -89,8 +89,8 @@ ... TODO: Get rid of this (def: monad - (:as (Monad Action) - (try.with async.monad))) + (as (Monad Action) + (try.with async.monad))) (with_expansions [<Platform> (as_is (Platform <type_vars>)) <State+> (as_is (///directive.State+ <type_vars>)) @@ -113,23 +113,23 @@ (-> context.Context <Platform> module.ID (Key document) (Writer document) (archive.Entry document) (Async (Try Any)))) (let [system (the #&file_system platform) - write_artifact! (: (-> [artifact.ID (Maybe Text) Binary] (Action Any)) - (function (_ [artifact_id custom content]) - (cache/artifact.cache! system context @module artifact_id content)))] + write_artifact! (is (-> [artifact.ID (Maybe Text) Binary] (Action Any)) + (function (_ [artifact_id custom content]) + (cache/artifact.cache! system context @module artifact_id content)))] (do [! ..monad] - [_ (: (Async (Try Any)) - (cache/module.enable! async.monad system context @module)) + [_ (is (Async (Try Any)) + (cache/module.enable! async.monad system context @module)) _ (for @.python (|> entry (the archive.#output) sequence.list (list.sub 128) (monad.each ! (monad.each ! write_artifact!)) - (: (Action (List (List Any))))) + (is (Action (List (List Any))))) (|> entry (the archive.#output) sequence.list (monad.each ..monad write_artifact!) - (: (Action (List Any))))) + (is (Action (List Any))))) document (# async.monad in (document.marked? key (the [archive.#module module.#document] entry)))] (|> [(|> entry @@ -203,22 +203,22 @@ .Lux <State+> (Try <State+>))) - (|> (:sharing [<type_vars>] - <State+> - state - - (///directive.Operation <type_vars> Any) - (do [! ///phase.monad] - [_ (///directive.lifted_analysis - (do ! - [_ (///analysis.set_state analysis_state)] - (extension.with extender analysers))) - _ (///directive.lifted_synthesis - (extension.with extender synthesizers)) - _ (///directive.lifted_generation - (extension.with extender (:expected generators))) - _ (extension.with extender (:expected directives))] - (in []))) + (|> (sharing [<type_vars>] + <State+> + state + + (///directive.Operation <type_vars> Any) + (do [! ///phase.monad] + [_ (///directive.lifted_analysis + (do ! + [_ (///analysis.set_state analysis_state)] + (extension.with extender analysers))) + _ (///directive.lifted_synthesis + (extension.with extender synthesizers)) + _ (///directive.lifted_generation + (extension.with extender (as_expected generators))) + _ (extension.with extender (as_expected directives))] + (in []))) (///phase.result' state) (# try.monad each product.left))) @@ -270,23 +270,23 @@ (the #host platform) (the #phase platform) generation_bundle)] - _ (: (Async (Try Any)) - (cache.enable! async.monad (the #&file_system platform) context)) + _ (is (Async (Try Any)) + (cache.enable! async.monad (the #&file_system platform) context)) [archive analysis_state bundles] (ioW.thaw (list) compilation_configuration (the #host platform) (the #&file_system platform) context import compilation_sources) .let [with_missing_extensions - (: (All (_ <type_vars>) - (-> <Platform> (Program expression directive) <State+> - (Async (Try [///phase.Wrapper <State+>])))) - (function (_ platform program state) - (async#in - (do try.monad - [[state phase_wrapper] (..phase_wrapper archive platform state)] - (|> state - (initialize_state (extender phase_wrapper) - (:expected (..complete_extensions host_directive_bundle phase_wrapper (:expected bundles))) - analysis_state) - (try#each (|>> (//init.with_default_directives expander host_analysis program anchorT,expressionT,directiveT (extender phase_wrapper)) - [phase_wrapper])))))))]] + (is (All (_ <type_vars>) + (-> <Platform> (Program expression directive) <State+> + (Async (Try [///phase.Wrapper <State+>])))) + (function (_ platform program state) + (async#in + (do try.monad + [[state phase_wrapper] (..phase_wrapper archive platform state)] + (|> state + (initialize_state (extender phase_wrapper) + (as_expected (..complete_extensions host_directive_bundle phase_wrapper (as_expected bundles))) + analysis_state) + (try#each (|>> (//init.with_default_directives expander host_analysis program anchorT,expressionT,directiveT (extender phase_wrapper)) + [phase_wrapper])))))))]] (if (archive.archived? archive descriptor.runtime) (do ! [[phase_wrapper state] (with_missing_extensions platform program state)] @@ -345,26 +345,26 @@ (def: (depend module import dependence) (-> descriptor.Module descriptor.Module Dependence Dependence) - (let [transitive_dependency (: (-> (-> Dependence Mapping) descriptor.Module (Set descriptor.Module)) - (function (_ lens module) - (|> dependence - lens - (dictionary.value module) - (maybe.else ..empty)))) + (let [transitive_dependency (is (-> (-> Dependence Mapping) descriptor.Module (Set descriptor.Module)) + (function (_ lens module) + (|> dependence + lens + (dictionary.value module) + (maybe.else ..empty)))) transitive_depends_on (transitive_dependency (the #depends_on) import) transitive_depended_by (transitive_dependency (the #depended_by) module) - update_dependence (: (-> [descriptor.Module (Set descriptor.Module)] [descriptor.Module (Set descriptor.Module)] - (-> Mapping Mapping)) - (function (_ [source forward] [target backward]) - (function (_ mapping) - (let [with_dependence+transitives - (|> mapping - (dictionary.revised' source ..empty (set.has target)) - (dictionary.revised source (set.union forward)))] - (list#mix (function (_ previous) - (dictionary.revised' previous ..empty (set.has target))) - with_dependence+transitives - (set.list backward))))))] + update_dependence (is (-> [descriptor.Module (Set descriptor.Module)] [descriptor.Module (Set descriptor.Module)] + (-> Mapping Mapping)) + (function (_ [source forward] [target backward]) + (function (_ mapping) + (let [with_dependence+transitives + (|> mapping + (dictionary.revised' source ..empty (set.has target)) + (dictionary.revised source (set.union forward)))] + (list#mix (function (_ previous) + (dictionary.revised' previous ..empty (set.has target))) + with_dependence+transitives + (set.list backward))))))] (|> dependence (revised #depends_on (update_dependence @@ -377,13 +377,13 @@ (def: (circular_dependency? module import dependence) (-> descriptor.Module descriptor.Module Dependence Bit) - (let [dependence? (: (-> descriptor.Module (-> Dependence Mapping) descriptor.Module Bit) - (function (_ from relationship to) - (let [targets (|> dependence - relationship - (dictionary.value from) - (maybe.else ..empty))] - (set.member? targets to))))] + (let [dependence? (is (-> descriptor.Module (-> Dependence Mapping) descriptor.Module Bit) + (function (_ from relationship to) + (let [targets (|> dependence + relationship + (dictionary.value from) + (maybe.else ..empty))] + (set.member? targets to))))] (or (dependence? import (the #depends_on) module) (dependence? module (the #depended_by) import)))) @@ -495,74 +495,74 @@ (-> Lux_Context (-> Lux_Compiler Lux_Importer))) (let [current (stm.var initial) - pending (:sharing [<type_vars>] - Lux_Context - initial - - (Var (Dictionary descriptor.Module Lux_Pending)) - (:expected (stm.var (dictionary.empty text.hash)))) - dependence (: (Var Dependence) - (stm.var ..independence))] + pending (sharing [<type_vars>] + Lux_Context + initial + + (Var (Dictionary descriptor.Module Lux_Pending)) + (as_expected (stm.var (dictionary.empty text.hash)))) + dependence (is (Var Dependence) + (stm.var ..independence))] (function (_ compile) (function (import! customs importer module) (do [! async.monad] - [[return signal] (:sharing [<type_vars>] - Lux_Context - initial - - (Async [Lux_Return (Maybe [Lux_Context - module.ID - Lux_Signal])]) - (:expected - (stm.commit! - (do [! stm.monad] - [dependence (if (text#= descriptor.runtime importer) - (stm.read dependence) - (do ! - [[_ dependence] (stm.update (..depend importer module) dependence)] - (in dependence)))] - (case (..verify_dependencies importer module dependence) - {try.#Failure error} - (in [(async.resolved {try.#Failure error}) - {.#None}]) - - {try.#Success _} - (do ! - [[archive state] (stm.read current)] - (if (archive.archived? archive module) - (in [(async#in {try.#Success [archive state]}) - {.#None}]) - (do ! - [@pending (stm.read pending)] - (case (dictionary.value module @pending) - {.#Some [return signal]} - (in [return - {.#None}]) - - {.#None} - (case (if (archive.reserved? archive module) - (do try.monad - [@module (archive.id module archive)] - (in [@module archive])) - (archive.reserve module archive)) - {try.#Success [@module archive]} - (do ! - [_ (stm.write [archive state] current) - .let [[return signal] (:sharing [<type_vars>] - Lux_Context - initial - - Lux_Pending - (async.async []))] - _ (stm.update (dictionary.has module [return signal]) pending)] - (in [return - {.#Some [[archive state] - @module - signal]}])) - - {try.#Failure error} - (in [(async#in {try.#Failure error}) - {.#None}]))))))))))) + [[return signal] (sharing [<type_vars>] + Lux_Context + initial + + (Async [Lux_Return (Maybe [Lux_Context + module.ID + Lux_Signal])]) + (as_expected + (stm.commit! + (do [! stm.monad] + [dependence (if (text#= descriptor.runtime importer) + (stm.read dependence) + (do ! + [[_ dependence] (stm.update (..depend importer module) dependence)] + (in dependence)))] + (case (..verify_dependencies importer module dependence) + {try.#Failure error} + (in [(async.resolved {try.#Failure error}) + {.#None}]) + + {try.#Success _} + (do ! + [[archive state] (stm.read current)] + (if (archive.archived? archive module) + (in [(async#in {try.#Success [archive state]}) + {.#None}]) + (do ! + [@pending (stm.read pending)] + (case (dictionary.value module @pending) + {.#Some [return signal]} + (in [return + {.#None}]) + + {.#None} + (case (if (archive.reserved? archive module) + (do try.monad + [@module (archive.id module archive)] + (in [@module archive])) + (archive.reserve module archive)) + {try.#Success [@module archive]} + (do ! + [_ (stm.write [archive state] current) + .let [[return signal] (sharing [<type_vars>] + Lux_Context + initial + + Lux_Pending + (async.async []))] + _ (stm.update (dictionary.has module [return signal]) pending)] + (in [return + {.#Some [[archive state] + @module + signal]}])) + + {try.#Failure error} + (in [(async#in {try.#Failure error}) + {.#None}]))))))))))) _ (case signal {.#None} (in []) @@ -600,23 +600,23 @@ .let [additions (|> modules (list#each product.left) (set.of_list text.hash)) - with_modules (: (All (_ <type_vars>) - (-> <State+> <State+>)) - (revised [extension.#state - ///directive.#analysis - ///directive.#state - extension.#state] - (: (All (_ a) (-> a a)) - (function (_ analysis_state) - (|> analysis_state - (:as .Lux) - (revised .#modules (function (_ current) - (list#composite (list.only (|>> product.left - (set.member? additions) - not) - current) - modules))) - :expected)))))] + with_modules (is (All (_ <type_vars>) + (-> <State+> <State+>)) + (revised [extension.#state + ///directive.#analysis + ///directive.#state + extension.#state] + (is (All (_ a) (-> a a)) + (function (_ analysis_state) + (|> analysis_state + (as .Lux) + (revised .#modules (function (_ current) + (list#composite (list.only (|>> product.left + (set.member? additions) + not) + current) + modules))) + as_expected)))))] state (monad.mix ! with_all_extensions state extended_states)] (in (with_modules state)))) @@ -633,18 +633,18 @@ ... This might not be the case in the future. (def: (with_new_dependencies new_dependencies all_dependencies) (-> (List descriptor.Module) (Set descriptor.Module) [(Set descriptor.Module) (Set descriptor.Module)]) - (let [[all_dependencies duplicates _] (: [(Set descriptor.Module) (Set descriptor.Module) Bit] - (list#mix (function (_ new [all duplicates seen_prelude?]) - (if (set.member? all new) - (if (text#= .prelude_module new) - (if seen_prelude? - [all (set.has new duplicates) seen_prelude?] - [all duplicates true]) - [all (set.has new duplicates) seen_prelude?]) - [(set.has new all) duplicates seen_prelude?])) - (: [(Set descriptor.Module) (Set descriptor.Module) Bit] - [all_dependencies ..empty (set.empty? all_dependencies)]) - new_dependencies))] + (let [[all_dependencies duplicates _] (is [(Set descriptor.Module) (Set descriptor.Module) Bit] + (list#mix (function (_ new [all duplicates seen_prelude?]) + (if (set.member? all new) + (if (text#= .prelude_module new) + (if seen_prelude? + [all (set.has new duplicates) seen_prelude?] + [all duplicates true]) + [all (set.has new duplicates) seen_prelude?]) + [(set.has new all) duplicates seen_prelude?])) + (is [(Set descriptor.Module) (Set descriptor.Module) Bit] + [all_dependencies ..empty (set.empty? all_dependencies)]) + new_dependencies))] [all_dependencies duplicates])) (def: (any|after_imports customs import! module duplicates new_dependencies archive) @@ -713,8 +713,8 @@ (function (_ customs importer import! @module [archive state] module) (loop [[archive state] [archive state] compilation custom_compilation - all_dependencies (: (Set descriptor.Module) - (set.of_list text.hash (list)))] + all_dependencies (is (Set descriptor.Module) + (set.of_list text.hash (list)))] (do [! (try.with async.monad)] [.let [new_dependencies (the ///.#dependencies compilation) [all_dependencies duplicates] (with_new_dependencies new_dependencies all_dependencies)] @@ -723,13 +723,13 @@ {try.#Success [state more|done]} (case more|done {.#Left more} - (let [continue! (:sharing [state document object] - (///.Compilation state document object) - custom_compilation - - (-> (..Context state) (///.Compilation state document object) (Set descriptor.Module) - (..Return state)) - (:expected again))] + (let [continue! (sharing [state document object] + (///.Compilation state document object) + custom_compilation + + (-> (..Context state) (///.Compilation state document object) (Set descriptor.Module) + (..Return state)) + (as_expected again))] (continue! [archive state] more all_dependencies)) {.#Right entry} @@ -753,8 +753,8 @@ (function (_ customs importer import! @module [archive state] module) (loop [[archive state] [archive (..set_current_module module state)] compilation compilation - all_dependencies (: (Set descriptor.Module) - (set.of_list text.hash (list)))] + all_dependencies (is (Set descriptor.Module) + (set.of_list text.hash (list)))] (do [! (try.with async.monad)] [.let [new_dependencies (the ///.#dependencies compilation) [all_dependencies duplicates] (with_new_dependencies new_dependencies all_dependencies)] @@ -763,13 +763,13 @@ {try.#Success [state more|done]} (case more|done {.#Left more} - (let [continue! (:sharing [<type_vars>] - <Platform> - platform - - (-> Lux_Context (///.Compilation <State+> .Module Any) (Set descriptor.Module) - (Action [Archive <State+>])) - (:expected again))] + (let [continue! (sharing [<type_vars>] + <Platform> + platform + + (-> Lux_Context (///.Compilation <State+> .Module Any) (Set descriptor.Module) + (Action [Archive <State+>])) + (as_expected again))] (continue! [archive state] more all_dependencies)) {.#Right entry} @@ -784,7 +784,7 @@ (console.write_line report console)) <else>))) .let [entry (has [archive.#module module.#descriptor descriptor.#references] all_dependencies entry)] - _ (..cache_module context platform @module $.key $.writer (:as (archive.Entry .Module) entry))] + _ (..cache_module context platform @module $.key $.writer (as (archive.Entry .Module) entry))] (async#in (do try.monad [archive (archive.has module entry archive)] (in [archive @@ -820,8 +820,8 @@ compilation_sources (the context.#host_module_extension context) module)] - (loop [customs (for @.old (:as (List (///.Custom Fake_State Fake_Document Fake_Object)) - all_customs) + (loop [customs (for @.old (as (List (///.Custom Fake_State Fake_Document Fake_Object)) + all_customs) all_customs)] (case customs {.#End} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux.lux index d5b883eed..f237ebeae 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux.lux @@ -22,24 +22,24 @@ ... TODO: Not just from this parser, but from the lux.Module type. (def: .public writer (Writer .Module) - (let [definition (: (Writer Definition) - ($_ _.and _.bit _.type _.any)) - labels (: (Writer [Text (List Text)]) - (_.and _.text (_.list _.text))) - global_type (: (Writer [Bit Type (Either [Text (List Text)] - [Text (List Text)])]) - ($_ _.and _.bit _.type (_.or labels labels))) - global_label (: (Writer .Label) - ($_ _.and _.bit _.type (_.list _.text) _.nat)) - alias (: (Writer Alias) - (_.and _.text _.text)) - global (: (Writer Global) - ($_ _.or - definition - global_type - global_label - global_label - alias))] + (let [definition (is (Writer Definition) + ($_ _.and _.bit _.type _.any)) + labels (is (Writer [Text (List Text)]) + (_.and _.text (_.list _.text))) + global_type (is (Writer [Bit Type (Either [Text (List Text)] + [Text (List Text)])]) + ($_ _.and _.bit _.type (_.or labels labels))) + global_label (is (Writer .Label) + ($_ _.and _.bit _.type (_.list _.text) _.nat)) + alias (is (Writer Alias) + (_.and _.text _.text)) + global (is (Writer Global) + ($_ _.or + definition + global_type + global_label + global_label + alias))] ($_ _.and ... #module_hash _.nat @@ -54,38 +54,38 @@ (def: .public parser (Parser .Module) - (let [definition (: (Parser Definition) - ($_ <>.and - <binary>.bit - <binary>.type - <binary>.any)) - labels (: (Parser [Text (List Text)]) - ($_ <>.and - <binary>.text - (<binary>.list <binary>.text))) - global_type (: (Parser [Bit Type (Either [Text (List Text)] - [Text (List Text)])]) + (let [definition (is (Parser Definition) ($_ <>.and <binary>.bit <binary>.type - (<binary>.or labels labels))) - global_label (: (Parser .Label) + <binary>.any)) + labels (is (Parser [Text (List Text)]) + ($_ <>.and + <binary>.text + (<binary>.list <binary>.text))) + global_type (is (Parser [Bit Type (Either [Text (List Text)] + [Text (List Text)])]) ($_ <>.and <binary>.bit <binary>.type - (<binary>.list <binary>.text) - <binary>.nat)) - alias (: (Parser Alias) - ($_ <>.and - <binary>.text - <binary>.text)) - global (: (Parser Global) - ($_ <binary>.or - definition - global_type - global_label - global_label - alias))] + (<binary>.or labels labels))) + global_label (is (Parser .Label) + ($_ <>.and + <binary>.bit + <binary>.type + (<binary>.list <binary>.text) + <binary>.nat)) + alias (is (Parser Alias) + ($_ <>.and + <binary>.text + <binary>.text)) + global (is (Parser Global) + ($_ <binary>.or + definition + global_type + global_label + global_label + alias))] ($_ <>.and ... #module_hash <binary>.nat diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux index 1828747ab..24c60d5fa 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis.lux @@ -160,8 +160,8 @@ (def: .public (reification analysis) (-> Analysis (Reification Analysis)) (loop [abstraction analysis - inputs (: (List Analysis) - (list))] + inputs (is (List Analysis) + (list))] (.case abstraction {#Apply input next} (again next {.#Item input inputs}) @@ -377,5 +377,5 @@ .#seed 0 .#scope_type_vars (list) .#extensions [] - .#eval (:as (-> Type Code (Meta Any)) []) + .#eval (as (-> Type Code (Meta Any)) []) .#host []]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux index 9c2aa022e..0484b5941 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/coverage.lux @@ -367,26 +367,26 @@ ... merges can be done. [_ {#Alt leftS rightS}] (do [! try.monad] - [.let [fuse_once (: (-> Coverage (List Coverage) - (Try [(Maybe Coverage) - (List Coverage)])) - (function (_ coverageA possibilitiesSF) - (loop [altsSF possibilitiesSF] - (case altsSF - {.#End} - (in [{.#None} (list coverageA)]) - - {.#Item altSF altsSF'} - (do ! - [altMSF (composite coverageA altSF)] - (case altMSF - {#Alt _} - (do ! - [[success altsSF+] (again altsSF')] - (in [success {.#Item altSF altsSF+}])) - - _ - (in [{.#Some altMSF} altsSF'])))))))]] + [.let [fuse_once (is (-> Coverage (List Coverage) + (Try [(Maybe Coverage) + (List Coverage)])) + (function (_ coverageA possibilitiesSF) + (loop [altsSF possibilitiesSF] + (case altsSF + {.#End} + (in [{.#None} (list coverageA)]) + + {.#Item altSF altsSF'} + (do ! + [altMSF (composite coverageA altSF)] + (case altMSF + {#Alt _} + (do ! + [[success altsSF+] (again altsSF')] + (in [success {.#Item altSF altsSF+}])) + + _ + (in [{.#Some altMSF} altsSF'])))))))]] (loop [addition addition possibilitiesSF (alternatives so_far)] (do ! diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux index 3ca408bea..de22db2db 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/evaluation.lux @@ -1,7 +1,7 @@ (.using [library [lux "*" - [type {"+" :sharing}] + [type {"+" sharing}] ["[0]" meta] [abstract [monad {"+" do}]] @@ -62,12 +62,12 @@ [exprS (|> exprA (synthesisP.phase archive) (phase.result synthesis_state))]) (phase.result generation_state) (do phase.monad - [@module (:sharing [anchor expression artifact] - (generation.Phase anchor expression artifact) - generate + [@module (sharing [anchor expression artifact] + (generation.Phase anchor expression artifact) + generate - (generation.Operation anchor expression artifact module.ID) - (generation.module_id module archive)) + (generation.Operation anchor expression artifact module.ID) + (generation.module_id module archive)) .let [[evals _] (io.run! (atom.update! (dictionary.revised' @module 0 ++) ..evals)) @eval (maybe.else 0 (dictionary.value @module evals))] exprO (<| (generation.with_registry_shift (|> @module diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux index 0d22a6790..1a95a5a2c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/module.lux @@ -99,8 +99,8 @@ [self_name meta.current_module_name] (function (_ state) {try.#Success [(revised .#modules - (plist.revised self_name (revised .#module_aliases (: (-> (List [Text Text]) (List [Text Text])) - (|>> {.#Item [alias module]})))) + (plist.revised self_name (revised .#module_aliases (is (-> (List [Text Text]) (List [Text Text])) + (|>> {.#Item [alias module]})))) state) []]})))) @@ -127,8 +127,8 @@ {try.#Success [(revised .#modules (plist.has self_name (revised .#definitions - (: (-> (List [Text Global]) (List [Text Global])) - (|>> {.#Item [name definition]})) + (is (-> (List [Text Global]) (List [Text Global])) + (|>> {.#Item [name definition]})) self)) state) []]} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux index 42ccf412d..6902cd718 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/scope.lux @@ -90,15 +90,15 @@ {.#Item top_outer _} (let [[ref_type init_ref] (maybe.else (undefined) (..reference name top_outer)) - [ref inner'] (list#mix (: (-> Scope [Variable (List Scope)] [Variable (List Scope)]) - (function (_ scope ref+inner) - [{variable.#Foreign (the [.#captured .#counter] scope)} - {.#Item (revised .#captured - (: (-> Foreign Foreign) - (|>> (revised .#counter ++) - (revised .#mappings (plist.has name [ref_type (product.left ref+inner)])))) - scope) - (product.right ref+inner)}])) + [ref inner'] (list#mix (is (-> Scope [Variable (List Scope)] [Variable (List Scope)]) + (function (_ scope ref+inner) + [{variable.#Foreign (the [.#captured .#counter] scope)} + {.#Item (revised .#captured + (is (-> Foreign Foreign) + (|>> (revised .#counter ++) + (revised .#mappings (plist.has name [ref_type (product.left ref+inner)])))) + scope) + (product.right ref+inner)}])) [init_ref {.#End}] (list.reversed inner)) scopes (list#composite inner' outer)] @@ -117,9 +117,9 @@ (let [old_mappings (the [.#locals .#mappings] head) new_var_id (the [.#locals .#counter] head) new_head (revised .#locals - (: (-> Local Local) - (|>> (revised .#counter ++) - (revised .#mappings (plist.has name [type new_var_id])))) + (is (-> Local Local) + (|>> (revised .#counter ++) + (revised .#mappings (plist.has name [type new_var_id])))) head)] (case (phase.result' [bundle (has .#scopes {.#Item new_head tail} state)] action) @@ -142,9 +142,9 @@ (def: empty Scope - (let [bindings (: Bindings - [.#counter 0 - .#mappings (list)])] + (let [bindings (is Bindings + [.#counter 0 + .#mappings (list)])] [.#name (list) .#inner 0 .#locals bindings diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux index 724d85a24..b215fa8b0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/type.lux @@ -84,7 +84,7 @@ ... (if (n.< (the .#var_counter post) ... pre#var_counter) ... (do ! - ... [.let [new! (: (-> [Nat (Maybe Type)] (Maybe Nat)) + ... [.let [new! (is (-> [Nat (Maybe Type)] (Maybe Nat)) ... (function (_ [id _]) ... (if (n.< id pre#var_counter) ... {.#Some id} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux index 706603273..2b9f8b598 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux @@ -57,19 +57,19 @@ (type: .public (Host expression directive) (Interface - (: (-> unit.ID [(Maybe unit.ID) expression] (Try Any)) - evaluate) - (: (-> directive (Try Any)) - execute) - (: (-> unit.ID (Maybe Text) [(Maybe unit.ID) expression] (Try [Text Any directive])) - define) - - (: (-> unit.ID Binary directive) - ingest) - (: (-> unit.ID (Maybe Text) directive (Try Any)) - re_learn) - (: (-> unit.ID (Maybe Text) directive (Try Any)) - re_load))) + (is (-> unit.ID [(Maybe unit.ID) expression] (Try Any)) + evaluate) + (is (-> directive (Try Any)) + execute) + (is (-> unit.ID (Maybe Text) [(Maybe unit.ID) expression] (Try [Text Any directive])) + define) + + (is (-> unit.ID Binary directive) + ingest) + (is (-> unit.ID (Maybe Text) directive (Try Any)) + re_learn) + (is (-> unit.ID (Maybe Text) directive (Try Any)) + re_load))) (type: .public (State anchor expression directive) (Record diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux index c999697dd..a35c61eb3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case.lux @@ -89,8 +89,8 @@ ... type-check the input with respect to the patterns. (def: .public (tuple :it:) (-> Type (Check [(List check.Var) Type])) - (loop [envs (: (List (List Type)) - (list)) + (loop [envs (is (List (List Type)) + (list)) :it: :it:] (.case :it: {.#Var id} @@ -167,8 +167,8 @@ {.#Product _} (let [matches (loop [types (type.flat_tuple :input:') patterns sub_patterns - output (: (List [Type Code]) - {.#End})] + output (is (List [Type Code]) + {.#End})] (.case [types patterns] [{.#End} {.#End}] output @@ -188,15 +188,15 @@ _ (undefined)))] (do ! - [[memberP+ thenA] (list#mix (: (All (_ a) - (-> [Type Code] (Operation [(List Pattern) a]) - (Operation [(List Pattern) a]))) - (function (_ [memberT memberC] then) - (do ! - [[memberP [memberP+ thenA]] ((:as (All (_ a) (-> (Maybe Nat) Type Code (Operation a) (Operation [Pattern a]))) + [[memberP+ thenA] (list#mix (is (All (_ a) + (-> [Type Code] (Operation [(List Pattern) a]) + (Operation [(List Pattern) a]))) + (function (_ [memberT memberC] then) + (do ! + [[memberP [memberP+ thenA]] ((as (All (_ a) (-> (Maybe Nat) Type Code (Operation a) (Operation [Pattern a]))) pattern_analysis) - {.#None} memberT memberC then)] - (in [(list& memberP memberP+) thenA])))) + {.#None} memberT memberC then)] + (in [(list& memberP memberP+) thenA])))) (do ! [nextA next] (in [(list) nextA])) @@ -253,13 +253,13 @@ (/.with_location location (do [! ///.monad] [record (//complex.normal true sub_patterns) - record_size,members,recordT (: (Operation (Maybe [Nat (List Code) Type])) - (.case record - {.#Some record} - (//complex.order true record) + record_size,members,recordT (is (Operation (Maybe [Nat (List Code) Type])) + (.case record + {.#Some record} + (//complex.order true record) - {.#None} - (in {.#None})))] + {.#None} + (in {.#None})))] (.case record_size,members,recordT {.#Some [record_size members recordT]} (do ! diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux index eb34d19c2..2a8279ae8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/complex.lux @@ -192,7 +192,7 @@ (-> Phase Type Archive (List Code) (Operation Analysis)) (<| (let [! ///.monad]) (# ! each (|>> /.tuple)) - (: (Operation (List Analysis))) + (is (Operation (List Analysis))) (loop [membersT+ (type.flat_tuple expectedT) membersC+ members] (case [membersT+ membersC+] @@ -293,8 +293,8 @@ (def: .public (normal pattern_matching? record) (-> Bit (List Code) (Operation (Maybe (List [Symbol Code])))) (loop [input record - output (: (List [Symbol Code]) - {.#End})] + output (is (List [Symbol Code]) + {.#End})] (case input (pattern (list& [_ {.#Symbol ["" slotH]}] valueH tail)) (if pattern_matching? @@ -352,8 +352,8 @@ {.#None} (/.except ..slot_does_not_belong_to_record [key recordT])))) - (: (Dictionary Nat Code) - (dictionary.empty n.hash)) + (is (Dictionary Nat Code) + (dictionary.empty n.hash)) record) .let [ordered_tuple (list#each (function (_ idx) (maybe.trusted (dictionary.value idx idx->val))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux index bfd85814a..eb3cfa9ba 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/directive.lux @@ -87,7 +87,7 @@ (the [//extension.#state /.#synthesis /.#state] state) (the [//extension.#state /.#generation /.#state] state) (the [//extension.#state /.#generation /.#phase] state))) - extension_eval (:as Eval (wrapper (:expected compiler_eval)))] + extension_eval (as Eval (wrapper (as_expected compiler_eval)))] _ (//.with (has [//extension.#state /.#analysis /.#state //extension.#state .#eval] extension_eval state))] (case code (pattern [_ {.#Form (list& [_ {.#Text name}] inputs)}]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux index 6a8793379..ea51560df 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/jvm.lux @@ -416,18 +416,18 @@ {.#None} (do [! phase.monad] - [parametersJT (: (Operation (List (Type Parameter))) - (monad.each ! - (function (_ parameterT) - (do phase.monad - [parameterJT (jvm_type parameterT)] - (case (parser.parameter? parameterJT) - {.#Some parameterJT} - (in parameterJT) - - {.#None} - (/////analysis.except ..non_parameter parameterT)))) - parametersT))] + [parametersJT (is (Operation (List (Type Parameter))) + (monad.each ! + (function (_ parameterT) + (do phase.monad + [parameterJT (jvm_type parameterT)] + (case (parser.parameter? parameterJT) + {.#Some parameterJT} + (in parameterJT) + + {.#None} + (/////analysis.except ..non_parameter parameterT)))) + parametersT))] (in (jvm.class class parametersJT)))) {.#Ex _} @@ -869,10 +869,10 @@ (analyse archive exceptionC)) [exception_class _] (check_object exceptionT) ? (phase.lifted (reflection!.sub? class_loader "java.lang.Throwable" exception_class)) - _ (: (Operation Any) - (if ? - (in []) - (/////analysis.except non_throwable exception_class)))] + _ (is (Operation Any) + (if ? + (in []) + (/////analysis.except non_throwable exception_class)))] (in {/////analysis.#Extension extension_name (list exceptionA)})) _ @@ -932,7 +932,7 @@ {.#None} (if (java/lang/reflect/Modifier::isInterface (java/lang/Class::getModifiers source_class)) - {.#Item (:as java/lang/reflect/Type (ffi.class_for java/lang/Object)) + {.#Item (as java/lang/reflect/Type (ffi.class_for java/lang/Object)) (array.list {.#None} (java/lang/Class::getGenericInterfaces source_class))} (array.list {.#None} (java/lang/Class::getGenericInterfaces source_class))))))) @@ -963,50 +963,50 @@ [fromT fromA] (typeA.inferring (analyse archive fromC)) source_name (# ! each ..reflection (check_jvm fromT)) - can_cast? (: (Operation Bit) - (`` (cond (~~ (template [<primitive> <object>] - [(let [=primitive (reflection.reflection <primitive>)] - (or (and (text#= =primitive source_name) - (or (text#= <object> target_name) - (text#= =primitive target_name))) - (and (text#= <object> source_name) - (text#= =primitive target_name)))) - (in true)] - - [reflection.boolean box.boolean] - [reflection.byte box.byte] - [reflection.short box.short] - [reflection.int box.int] - [reflection.long box.long] - [reflection.float box.float] - [reflection.double box.double] - [reflection.char box.char])) - - ... else - (do ! - [_ (phase.assertion ..primitives_are_not_objects [source_name] - (not (dictionary.key? ..boxes source_name))) - _ (phase.assertion ..primitives_are_not_objects [target_name] - (not (dictionary.key? ..boxes target_name))) - target_class (phase.lifted (reflection!.load class_loader target_name)) - _ (do ! - [source_class (phase.lifted (reflection!.load class_loader source_name))] - (phase.assertion ..cannot_cast [fromT toT fromC] - (java/lang/Class::isAssignableFrom source_class target_class)))] - (loop [[current_name currentT] [source_name fromT]] - (if (text#= target_name current_name) - (in true) - (do ! - [candidate_parents (: (Operation (List [[Text .Type] Bit])) - (class_candidate_parents class_loader current_name currentT target_name target_class))] - (case (|> candidate_parents - (list.only product.right) - (list#each product.left)) - {.#Item [next_name nextT] _} - (again [next_name nextT]) - - {.#End} - (in false)))))))))] + can_cast? (is (Operation Bit) + (`` (cond (~~ (template [<primitive> <object>] + [(let [=primitive (reflection.reflection <primitive>)] + (or (and (text#= =primitive source_name) + (or (text#= <object> target_name) + (text#= =primitive target_name))) + (and (text#= <object> source_name) + (text#= =primitive target_name)))) + (in true)] + + [reflection.boolean box.boolean] + [reflection.byte box.byte] + [reflection.short box.short] + [reflection.int box.int] + [reflection.long box.long] + [reflection.float box.float] + [reflection.double box.double] + [reflection.char box.char])) + + ... else + (do ! + [_ (phase.assertion ..primitives_are_not_objects [source_name] + (not (dictionary.key? ..boxes source_name))) + _ (phase.assertion ..primitives_are_not_objects [target_name] + (not (dictionary.key? ..boxes target_name))) + target_class (phase.lifted (reflection!.load class_loader target_name)) + _ (do ! + [source_class (phase.lifted (reflection!.load class_loader source_name))] + (phase.assertion ..cannot_cast [fromT toT fromC] + (java/lang/Class::isAssignableFrom source_class target_class)))] + (loop [[current_name currentT] [source_name fromT]] + (if (text#= target_name current_name) + (in true) + (do ! + [candidate_parents (is (Operation (List [[Text .Type] Bit])) + (class_candidate_parents class_loader current_name currentT target_name target_class))] + (case (|> candidate_parents + (list.only product.right) + (list#each product.left)) + {.#Item [next_name nextT] _} + (again [next_name nextT]) + + {.#End} + (in false)))))))))] (if can_cast? (in {/////analysis.#Extension extension_name (list (/////analysis.text source_name) (/////analysis.text target_name) @@ -1150,13 +1150,13 @@ (case (parser.class? it) {.#Some [name parameters]} (|> parameters - (list#each (|>> again (:as (Type Parameter)))) + (list#each (|>> again (as (Type Parameter)))) (jvm.class name)) {.#None}) (~~ (template [<read> <as> <write>] [(case (<read> it) {.#Some :sub:} - (<write> (:as (Type <as>) (again :sub:))) + (<write> (as (Type <as>) (again :sub:))) {.#None})] [parser.array? Value jvm.array] @@ -1381,17 +1381,17 @@ java/lang/Class::getDeclaredMethods (array.list {.#None}) (list.only (|>> java/lang/reflect/Method::getName (text#= method_name))) - (monad.each ! (: (-> java/lang/reflect/Method (Operation Evaluation)) - (function (_ method) - (do ! - [.let [expected_method_tvars (method_type_variables method) - aliasing (dictionary.merged (..aliasing expected_class_tvars actual_class_tvars) - (..aliasing expected_method_tvars actual_method_tvars))] - passes? (check_method aliasing class method_name method_style inputsJT method)] - (# ! each (if passes? - (|>> {#Pass}) - (|>> {#Hint})) - (method_signature method_style method)))))))] + (monad.each ! (is (-> java/lang/reflect/Method (Operation Evaluation)) + (function (_ method) + (do ! + [.let [expected_method_tvars (method_type_variables method) + aliasing (dictionary.merged (..aliasing expected_class_tvars actual_class_tvars) + (..aliasing expected_method_tvars actual_method_tvars))] + passes? (check_method aliasing class method_name method_style inputsJT method)] + (# ! each (if passes? + (|>> {#Pass}) + (|>> {#Hint})) + (method_signature method_style method)))))))] (case (list.all pass! candidates) {.#Item method {.#End}} (in method) @@ -1732,9 +1732,9 @@ (template [<name>] [(exception: .public (<name> [expected (List [(Type Class) Text (Type Method)]) actual (List [(Type Class) Text (Type Method)])]) - (let [%method (: (%.Format [(Type Class) Text (Type Method)]) - (function (_ [super name type]) - (format (..signature super) " :: " (%.text name) " " (..signature type))))] + (let [%method (is (%.Format [(Type Class) Text (Type Method)]) + (function (_ [super name type]) + (format (..signature super) " :: " (%.text name) " " (..signature type))))] (exception.report "Expected Methods" (exception.listing %method expected) "Actual Methods" (exception.listing %method actual))))] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux index 6c3e7c9fc..a85e87d85 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/analysis/lux.lux @@ -167,7 +167,7 @@ (case args (pattern (list typeC valueC)) (do [! ////.monad] - [actualT (# ! each (|>> (:as Type)) + [actualT (# ! each (|>> (as Type)) (eval archive Type typeC)) _ (typeA.inference actualT)] (<| (typeA.expecting actualT) @@ -182,7 +182,7 @@ (case args (pattern (list typeC valueC)) (do [! ////.monad] - [actualT (# ! each (|>> (:as Type)) + [actualT (# ! each (|>> (as Type)) (eval archive Type typeC)) _ (typeA.inference actualT) [valueT valueA] (typeA.inferring @@ -219,7 +219,7 @@ (case input_type (^.or {.#Definition [exported? def_type def_value]} {.#Type [exported? def_value labels]}) - (in (:as Type def_value)) + (in (as Type def_value)) (^.or {.#Tag _} {.#Slot _}) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux index a35443c11..0ec22f549 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/jvm.lux @@ -452,7 +452,7 @@ (list#mix (function (_ [lux_register type] [jvm_register before]) (let [[jvm_register' after] (method_argument (n.+ offset lux_register) type jvm_register)] [jvm_register' ($_ _.composite before after)])) - (: [Register (Bytecode Any)] [offset (_#in [])])) + (is [Register (Bytecode Any)] [offset (_#in [])])) product.right)) (def: (constructor_method_generation archive super_class method) @@ -645,26 +645,26 @@ (-> (Method_Definition Code) (Operation [(Set unit.ID) (Resource Method)]))) (function (_ methodC) (do phase.monad - [methodA (: (Operation Analysis) - (directive.lifted_analysis - (case methodC - {#Constructor method} - (jvm.analyse_constructor_method analyse archive selfT mapping method) - - {#Virtual_Method method} - (jvm.analyse_virtual_method analyse archive selfT mapping method) - - {#Static_Method method} - (jvm.analyse_static_method analyse archive mapping method) - - {#Overriden_Method method} - (jvm.analyse_overriden_method analyse archive selfT mapping (list& super interfaces) method) - - {#Abstract_Method method} - (jvm.analyse_abstract_method analyse archive method)))) - methodS (: (Operation Synthesis) - (directive.lifted_synthesis - (synthesize archive methodA))) + [methodA (is (Operation Analysis) + (directive.lifted_analysis + (case methodC + {#Constructor method} + (jvm.analyse_constructor_method analyse archive selfT mapping method) + + {#Virtual_Method method} + (jvm.analyse_virtual_method analyse archive selfT mapping method) + + {#Static_Method method} + (jvm.analyse_static_method analyse archive mapping method) + + {#Overriden_Method method} + (jvm.analyse_overriden_method analyse archive selfT mapping (list& super interfaces) method) + + {#Abstract_Method method} + (jvm.analyse_abstract_method analyse archive method)))) + methodS (is (Operation Synthesis) + (directive.lifted_synthesis + (synthesize archive methodA))) dependencies (directive.lifted_generation (cache.dependencies archive methodS)) methodS' (|> methodS diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux index a76c39427..16bd430fa 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux @@ -28,7 +28,7 @@ [math [number ["n" nat]]] - ["[0]" type {"+" :sharing} ("[1]#[0]" equivalence) + ["[0]" type {"+" sharing} ("[1]#[0]" equivalence) ["[0]" check]]]] ["[0]" /// {"+" Extender} ["[1][0]" bundle] @@ -230,10 +230,10 @@ previous_analysis_extensions (the [/////directive.#analysis /////directive.#state ///.#bundle] state)]] (phase.with [bundle (revised [/////directive.#analysis /////directive.#state] - (: (-> /////analysis.State+ /////analysis.State+) - (|>> product.right - [(|> previous_analysis_extensions - (dictionary.merged (///analysis.bundle eval host_analysis)))])) + (is (-> /////analysis.State+ /////analysis.State+) + (|>> product.right + [(|> previous_analysis_extensions + (dictionary.merged (///analysis.bundle eval host_analysis)))])) state)]))) (def: (announce_definition! short type) @@ -254,7 +254,7 @@ [type valueT value] (..definition archive full_name {.#None} valueC) [_ _ exported?] (evaluate! archive Bit exported?C) _ (/////directive.lifted_analysis - (moduleA.define short_name {.#Definition [(:as Bit exported?) type value]})) + (moduleA.define short_name {.#Definition [(as Bit exported?) type value]})) _ (..refresh expander host_analysis) _ (..announce_definition! short_name type)] (in /////directive.no_requirements)) @@ -284,7 +284,7 @@ (///.lifted meta.current_module_name)) .let [full_name [current_module short_name]] [_ _ exported?] (evaluate! archive Bit exported?C) - .let [exported? (:as Bit exported?)] + .let [exported? (as Bit exported?)] [type valueT value] (..definition archive full_name {.#Some .Type} valueC) labels (/////directive.lifted_analysis (do phase.monad @@ -299,14 +299,14 @@ (moduleA.define short_name {.#Definition [exported? type value]}) {.#Item labels} - (moduleA.define short_name {.#Type [exported? (:as .Type value) (if record? - {.#Right labels} - {.#Left labels})]})) - _ (moduleA.declare_labels record? labels exported? (:as .Type value))] + (moduleA.define short_name {.#Type [exported? (as .Type value) (if record? + {.#Right labels} + {.#Left labels})]})) + _ (moduleA.declare_labels record? labels exported? (as .Type value))] (in labels))) _ (..refresh expander host_analysis) _ (..announce_definition! short_name type) - _ (..announce_labels! labels (:as Type value))] + _ (..announce_labels! labels (as Type value))] (in /////directive.no_requirements)))])) (def: imports @@ -431,7 +431,7 @@ [target_platform (/////directive.lifted_analysis (///.lifted meta.target)) [_ _ name] (evaluate! archive Text nameC) - [_ handlerV] (<definer> archive (:as Text name) + [_ handlerV] (<definer> archive (as Text name) (let [raw_type (type <def_type>)] (case target_platform (^.or (pattern (static @.jvm)) @@ -445,15 +445,15 @@ (swapped binary.Binary Binary|DEFAULT raw_type))) valueC) _ (<| <scope> - (///.install extender (:as Text name)) - (:sharing [anchor expression directive] - (Handler anchor expression directive) - handler - - <type> - (:expected handlerV))) + (///.install extender (as Text name)) + (sharing [anchor expression directive] + (Handler anchor expression directive) + handler + + <type> + (as_expected handlerV))) _ (/////directive.lifted_generation - (/////generation.log! (format <description> " " (%.text (:as Text name)))))] + (/////generation.log! (format <description> " " (%.text (as Text name)))))] (in /////directive.no_requirements)) _ diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux index 61f03e588..987ae0104 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/common_lisp/common.lux @@ -1,42 +1,42 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" function] - ["[0]" try] - ["<>" parser - ["<s>" synthesis {"+" Parser}]]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" dictionary] - ["[0]" set] - ["[0]" list ("[1]#[0]" functor mix)]]] - [math - [number - ["f" frac]]] - ["@" target - ["_" common_lisp {"+" Expression}]]]] - ["[0]" //// "_" - ["/" bundle] - ["/[1]" // "_" - ["[0]" extension] - [generation - [extension {"+" Nullary Unary Binary Trinary - nullary unary binary trinary}] - ["[0]" reference] - ["//" common_lisp "_" - ["[1][0]" runtime {"+" Operation Phase Handler Bundle Generator}] - ["[1][0]" case]]] - [// - ["[0]" synthesis {"+" %synthesis}] - ["[0]" generation] - [/// - ["[1]" phase]]]]]) + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" function] + ["[0]" try] + ["<>" parser + ["<s>" synthesis {"+" Parser}]]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" dictionary] + ["[0]" set] + ["[0]" list ("[1]#[0]" functor mix)]]] + [math + [number + ["f" frac]]] + ["@" target + ["_" common_lisp {"+" Expression}]]]] + ["[0]" //// "_" + ["/" bundle] + ["/[1]" // "_" + ["[0]" extension] + [generation + [extension {"+" Nullary Unary Binary Trinary + nullary unary binary trinary}] + ["[0]" reference] + ["//" common_lisp "_" + ["[1][0]" runtime {"+" Operation Phase Handler Bundle Generator}] + ["[1][0]" case]]] + [// + ["[0]" synthesis {"+" %synthesis}] + ["[0]" generation] + [/// + ["[1]" phase]]]]]) (def: .public (custom [parser handler]) (All (_ s) @@ -67,7 +67,7 @@ ... [@input (# ! each _.var (generation.symbol "input")) ... inputG (phase archive input) ... elseG (phase archive else) -... conditionalsG (: (Operation (List [Expression Expression])) +... conditionalsG (is (Operation (List [Expression Expression])) ... (monad.each ! (function (_ [chars branch]) ... (do ! ... [branchG (phase archive branch)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux index 8f4bec35c..121fd29fa 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/common.lux @@ -105,7 +105,7 @@ {synthesis.#Extension "lux syntax char case!" parameters} (do /////.monad [body (expression archive synthesis)] - (in (:as Statement body))) + (in (as Statement body))) (^.template [<tag>] [(pattern (<tag> value)) @@ -159,21 +159,21 @@ (do [! /////.monad] [inputG (phase archive input) else! (..statement phase archive else) - conditionals! (: (Operation (List [(List Literal) - Statement])) - (monad.each ! (function (_ [chars branch]) - (do ! - [branch! (..statement phase archive branch)] - (in [(list#each (|>> .int _.int) chars) - branch!]))) - conditionals))] + conditionals! (is (Operation (List [(List Literal) + Statement])) + (monad.each ! (function (_ [chars branch]) + (do ! + [branch! (..statement phase archive branch)] + (in [(list#each (|>> .int _.int) chars) + branch!]))) + conditionals))] ... (in (_.apply/* (_.closure (list) ... (_.switch (_.the //runtime.i64_low_field inputG) ... conditionals! ... {.#Some (_.return else!)})) ... (list))) - (in (<| (:as Expression) - (: Statement) + (in (<| (as Expression) + (is Statement) (_.switch (_.the //runtime.i64_low_field inputG) conditionals! {.#Some else!})))))])) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux index 9f6f59ab9..77908df35 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/js/host.lux @@ -132,9 +132,9 @@ (function (_ extension phase archive [arity abstractionS]) (do [! ////////phase.monad] [abstractionG (phase archive abstractionS) - .let [variable (: (-> Text (Operation Var)) - (|>> generation.symbol - (# ! each _.var)))] + .let [variable (is (-> Text (Operation Var)) + (|>> generation.symbol + (# ! each _.var)))] g!inputs (monad.each ! (function (_ _) (variable "input")) (list.repeated (.nat arity) [])) g!abstraction (variable "abstraction")] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux index aa59d8b01..becc799b6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/common.lux @@ -106,20 +106,20 @@ [@end ///runtime.forge_label inputG (phase archive inputS) elseG (phase archive elseS) - conditionalsG+ (: (Operation (List [(List [S4 Label]) - (Bytecode Any)])) - (monad.each ! (function (_ [chars branch]) - (do ! - [branchG (phase archive branch) - @branch ///runtime.forge_label] - (in [(list#each (function (_ char) - [(try.trusted (signed.s4 (.int char))) @branch]) - chars) - ($_ _.composite - (_.set_label @branch) - branchG - (_.when_continuous (_.goto @end)))]))) - conditionalsS)) + conditionalsG+ (is (Operation (List [(List [S4 Label]) + (Bytecode Any)])) + (monad.each ! (function (_ [chars branch]) + (do ! + [branchG (phase archive branch) + @branch ///runtime.forge_label] + (in [(list#each (function (_ char) + [(try.trusted (signed.s4 (.int char))) @branch]) + chars) + ($_ _.composite + (_.set_label @branch) + branchG + (_.when_continuous (_.goto @end)))]))) + conditionalsS)) .let [table (|> conditionalsG+ (list#each product.left) list#conjoint) @@ -154,7 +154,7 @@ (def: bundle::lux Bundle - (|> (: Bundle /////bundle.empty) + (|> (is Bundle /////bundle.empty) (/////bundle.install "syntax char case!" ..lux::syntax_char_case!) (/////bundle.install "is" (binary ..lux::is)) (/////bundle.install "try" (unary ..lux::try)))) @@ -266,7 +266,7 @@ (def: bundle::i64 Bundle (<| (/////bundle.prefix "i64") - (|> (: Bundle /////bundle.empty) + (|> (is Bundle /////bundle.empty) (/////bundle.install "and" (binary ..i64::and)) (/////bundle.install "or" (binary ..i64::or)) (/////bundle.install "xor" (binary ..i64::xor)) @@ -285,7 +285,7 @@ (def: bundle::f64 Bundle (<| (/////bundle.prefix "f64") - (|> (: Bundle /////bundle.empty) + (|> (is Bundle /////bundle.empty) (/////bundle.install "+" (binary ..f64::+)) (/////bundle.install "-" (binary ..f64::-)) (/////bundle.install "*" (binary ..f64::*)) @@ -368,7 +368,7 @@ (def: bundle::text Bundle (<| (/////bundle.prefix "text") - (|> (: Bundle /////bundle.empty) + (|> (is Bundle /////bundle.empty) (/////bundle.install "=" (binary ..text::=)) (/////bundle.install "<" (binary ..text::<)) (/////bundle.install "concat" (binary ..text::concat)) @@ -400,7 +400,7 @@ (def: bundle::io Bundle (<| (/////bundle.prefix "io") - (|> (: Bundle /////bundle.empty) + (|> (is Bundle /////bundle.empty) (/////bundle.install "log" (unary ..io::log)) (/////bundle.install "error" (unary ..io::error))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux index a89e094ea..081984baf 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/jvm/host.lux @@ -135,7 +135,7 @@ (def: bundle::conversion Bundle (<| (/////bundle.prefix "conversion") - (|> (: Bundle /////bundle.empty) + (|> (is Bundle /////bundle.empty) (/////bundle.install "double-to-float" (unary conversion::double_to_float)) (/////bundle.install "double-to-int" (unary conversion::double_to_int)) (/////bundle.install "double-to-long" (unary conversion::double_to_long)) @@ -271,7 +271,7 @@ (def: bundle::int Bundle (<| (/////bundle.prefix (reflection.reflection reflection.int)) - (|> (: Bundle /////bundle.empty) + (|> (is Bundle /////bundle.empty) (/////bundle.install "+" (binary int::+)) (/////bundle.install "-" (binary int::-)) (/////bundle.install "*" (binary int::*)) @@ -290,7 +290,7 @@ (def: bundle::long Bundle (<| (/////bundle.prefix (reflection.reflection reflection.long)) - (|> (: Bundle /////bundle.empty) + (|> (is Bundle /////bundle.empty) (/////bundle.install "+" (binary long::+)) (/////bundle.install "-" (binary long::-)) (/////bundle.install "*" (binary long::*)) @@ -309,7 +309,7 @@ (def: bundle::float Bundle (<| (/////bundle.prefix (reflection.reflection reflection.float)) - (|> (: Bundle /////bundle.empty) + (|> (is Bundle /////bundle.empty) (/////bundle.install "+" (binary float::+)) (/////bundle.install "-" (binary float::-)) (/////bundle.install "*" (binary float::*)) @@ -322,7 +322,7 @@ (def: bundle::double Bundle (<| (/////bundle.prefix (reflection.reflection reflection.double)) - (|> (: Bundle /////bundle.empty) + (|> (is Bundle /////bundle.empty) (/////bundle.install "+" (binary double::+)) (/////bundle.install "-" (binary double::-)) (/////bundle.install "*" (binary double::*)) @@ -335,7 +335,7 @@ (def: bundle::char Bundle (<| (/////bundle.prefix (reflection.reflection reflection.char)) - (|> (: Bundle /////bundle.empty) + (|> (is Bundle /////bundle.empty) (/////bundle.install "=" (binary char::=)) (/////bundle.install "<" (binary char::<)) ))) @@ -634,7 +634,7 @@ (def: bundle::object Bundle (<| (/////bundle.prefix "object") - (|> (: Bundle /////bundle.empty) + (|> (is Bundle /////bundle.empty) (/////bundle.install "null" (nullary object::null)) (/////bundle.install "null?" (unary object::null?)) (/////bundle.install "synchronized" (binary object::synchronized)) @@ -790,17 +790,17 @@ (def: bundle::member Bundle (<| (/////bundle.prefix "member") - (|> (: Bundle /////bundle.empty) + (|> (is Bundle /////bundle.empty) (dictionary.merged (<| (/////bundle.prefix "get") - (|> (: Bundle /////bundle.empty) + (|> (is Bundle /////bundle.empty) (/////bundle.install "static" get::static) (/////bundle.install "virtual" get::virtual)))) (dictionary.merged (<| (/////bundle.prefix "put") - (|> (: Bundle /////bundle.empty) + (|> (is Bundle /////bundle.empty) (/////bundle.install "static" put::static) (/////bundle.install "virtual" put::virtual)))) (dictionary.merged (<| (/////bundle.prefix "invoke") - (|> (: Bundle /////bundle.empty) + (|> (is Bundle /////bundle.empty) (/////bundle.install "static" invoke::static) (/////bundle.install "virtual" invoke::virtual) (/////bundle.install "special" invoke::special) @@ -832,7 +832,7 @@ hidden [_ {//////synthesis.#Control {//////synthesis.#Branch {//////synthesis.#Case _ path}}}] - (loop [path (: Path path)] + (loop [path (is Path path)] (case path {//////synthesis.#Seq _ next} (again next) @@ -1133,9 +1133,9 @@ ($_ _.composite before after)])) - (: [Register (Bytecode Any)] - [offset - (_#in [])])) + (is [Register (Bytecode Any)] + [offset + (_#in [])])) product.right)) (def: (normalized_method global_mapping [environment method]) @@ -1241,7 +1241,7 @@ (def: bundle::class Bundle (<| (/////bundle.prefix "class") - (|> (: Bundle /////bundle.empty) + (|> (is Bundle /////bundle.empty) (/////bundle.install "anonymous" class::anonymous) ))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux index e8be23f6c..bb9c71927 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/common.lux @@ -66,7 +66,7 @@ {synthesis.#Extension "lux syntax char case!" parameters} (do /////.monad [body (expression archive synthesis)] - (in (:as Statement body))) + (in (as Statement body))) (^.template [<tag>] [(pattern (<tag> value)) @@ -138,7 +138,7 @@ {synthesis.#Then else}) [input] (//case.case! statement phase archive) - (# /////.monad each (|>> (:as Expression)))))])) + (# /////.monad each (|>> (as Expression)))))])) (def: lux_procs Bundle diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux index 23469d067..74540b895 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/lua/host.lux @@ -1,37 +1,37 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" function] - ["<>" parser - ["<s>" synthesis {"+" Parser}]]] - [data - [collection - ["[0]" dictionary] - ["[0]" list]] - [text - ["%" format {"+" format}]]] - [target - ["_" lua {"+" Var Expression}]]]] - ["[0]" // "_" - ["[1][0]" common {"+" custom}] - ["//[1]" /// "_" - ["/" bundle] + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" function] + ["<>" parser + ["<s>" synthesis {"+" Parser}]]] + [data + [collection + ["[0]" dictionary] + ["[0]" list]] + [text + ["%" format {"+" format}]]] + [target + ["_" lua {"+" Var Expression}]]]] + ["[0]" // "_" + ["[1][0]" common {"+" custom}] + ["//[1]" /// "_" + ["/" bundle] + ["/[1]" // "_" + ["[0]" extension] + [generation + [extension {"+" Nullary Unary Binary Trinary + nullary unary binary trinary}] + ["[0]" reference] + ["//" lua "_" + ["[1][0]" runtime {"+" Operation Phase Handler Bundle + with_vars}]]] ["/[1]" // "_" - ["[0]" extension] - [generation - [extension {"+" Nullary Unary Binary Trinary - nullary unary binary trinary}] - ["[0]" reference] - ["//" lua "_" - ["[1][0]" runtime {"+" Operation Phase Handler Bundle - with_vars}]]] - ["/[1]" // "_" - ["[0]" generation] - ["//[1]" /// "_" - ["[1][0]" phase]]]]]]) + ["[0]" generation] + ["//[1]" /// "_" + ["[1][0]" phase]]]]]]) (def: array::new (Unary Expression) @@ -170,9 +170,9 @@ (function (_ extension phase archive [arity abstractionS]) (do [! ////////phase.monad] [abstractionG (phase archive abstractionS) - .let [variable (: (-> Text (Operation Var)) - (|>> generation.symbol - (# ! each _.var)))] + .let [variable (is (-> Text (Operation Var)) + (|>> generation.symbol + (# ! each _.var)))] g!inputs (monad.each ! (function (_ _) (variable "input")) (list.repeated (.nat arity) []))] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux index 503b85252..2e6338e37 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/php/common.lux @@ -1,42 +1,42 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" function] - ["[0]" try] - ["<>" parser - ["<s>" synthesis {"+" Parser}]]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" dictionary] - ["[0]" set] - ["[0]" list ("[1]#[0]" functor mix)]]] - [math - [number - ["f" frac]]] - ["@" target - ["_" php {"+" Expression}]]]] - ["[0]" //// "_" - ["/" bundle] - ["/[1]" // "_" - ["[0]" extension] - [generation - [extension {"+" Nullary Unary Binary Trinary - nullary unary binary trinary}] - ["[0]" reference] - ["//" php "_" - ["[1][0]" runtime {"+" Operation Phase Handler Bundle Generator}] - ["[1][0]" case]]] - [// - ["[0]" synthesis {"+" %synthesis}] - ["[0]" generation] - [/// - ["[1]" phase]]]]]) + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" function] + ["[0]" try] + ["<>" parser + ["<s>" synthesis {"+" Parser}]]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" dictionary] + ["[0]" set] + ["[0]" list ("[1]#[0]" functor mix)]]] + [math + [number + ["f" frac]]] + ["@" target + ["_" php {"+" Expression}]]]] + ["[0]" //// "_" + ["/" bundle] + ["/[1]" // "_" + ["[0]" extension] + [generation + [extension {"+" Nullary Unary Binary Trinary + nullary unary binary trinary}] + ["[0]" reference] + ["//" php "_" + ["[1][0]" runtime {"+" Operation Phase Handler Bundle Generator}] + ["[1][0]" case]]] + [// + ["[0]" synthesis {"+" %synthesis}] + ["[0]" generation] + [/// + ["[1]" phase]]]]]) (def: .public (custom [parser handler]) (All (_ s) @@ -68,19 +68,19 @@ [[context_module context_artifact] elseG] (generation.with_new_context archive (phase archive else)) @input (# ! each _.var (generation.symbol "input")) - conditionalsG (: (Operation (List [Expression Expression])) - (monad.each ! (function (_ [chars branch]) - (do ! - [branchG (phase archive branch)] - (in [(|> chars - (list#each (|>> .int _.int (_.=== @input))) - (list#mix (function (_ clause total) - (if (same? _.null total) - clause - (_.or clause total))) - _.null)) - branchG]))) - conditionals)) + conditionalsG (is (Operation (List [Expression Expression])) + (monad.each ! (function (_ [chars branch]) + (do ! + [branchG (phase archive branch)] + (in [(|> chars + (list#each (|>> .int _.int (_.=== @input))) + (list#mix (function (_ clause total) + (if (same? _.null total) + clause + (_.or clause total))) + _.null)) + branchG]))) + conditionals)) .let [foreigns (|> conditionals (list#each (|>> product.right synthesis.path/then //case.dependencies)) (list& (//case.dependencies (synthesis.path/then else))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux index 481eefce0..dc6845bc8 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/common.lux @@ -52,7 +52,7 @@ {synthesis.#Extension "lux syntax char case!" parameters} (do /////.monad [body (expression archive synthesis)] - (in (:as (Statement Any) body))) + (in (as (Statement Any) body))) (^.template [<tag>] [(pattern (<tag> value)) @@ -114,20 +114,20 @@ [inputG (phase archive input) else! (..statement phase archive else) @input (# ! each _.var (generation.symbol "input")) - conditionals! (: (Operation (List [(Expression Any) - (Statement Any)])) - (monad.each ! (function (_ [chars branch]) - (do ! - [branch! (..statement phase archive branch)] - (in [(|> chars - (list#each (|>> .int _.int (_.= @input))) - (list#mix (function (_ clause total) - (if (same? _.none total) - clause - (_.or clause total))) - _.none)) - branch!]))) - conditionals)) + conditionals! (is (Operation (List [(Expression Any) + (Statement Any)])) + (monad.each ! (function (_ [chars branch]) + (do ! + [branch! (..statement phase archive branch)] + (in [(|> chars + (list#each (|>> .int _.int (_.= @input))) + (list#mix (function (_ clause total) + (if (same? _.none total) + clause + (_.or clause total))) + _.none)) + branch!]))) + conditionals)) ... .let [dependencies (//case.dependencies (list#mix (function (_ right left) ... (synthesis.path/seq left right)) ... (synthesis.path/then input) @@ -147,8 +147,8 @@ ... _ (generation.save! (product.right artifact_id) {.#None} closure) ] ... (in (_.apply/* @closure dependencies)) - (in (<| (:as (Expression Any)) - (: (Statement Any)) + (in (<| (as (Expression Any)) + (is (Statement Any)) ($_ _.then (_.set (list @input) inputG) (list#mix (function (_ [test then!] else!) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux index fa18710f9..72ade0f7d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/python/host.lux @@ -132,9 +132,9 @@ (function (_ extension phase archive [arity abstractionS]) (do [! ////////phase.monad] [abstractionG (phase archive abstractionS) - .let [variable (: (-> Text (Operation SVar)) - (|>> generation.symbol - (# ! each _.var)))] + .let [variable (is (-> Text (Operation SVar)) + (|>> generation.symbol + (# ! each _.var)))] g!inputs (monad.each ! (function (_ _) (variable "input")) (list.repeated (.nat arity) []))] (in (_.lambda g!inputs diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux index 492d9954f..e3beeba75 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/r/common.lux @@ -1,42 +1,42 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" function] - ["[0]" try] - ["<>" parser - ["<s>" synthesis {"+" Parser}]]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" dictionary] - ["[0]" set] - ["[0]" list ("[1]#[0]" functor mix)]]] - [math - [number - ["f" frac]]] - ["@" target - ["_" r {"+" Expression}]]]] - ["[0]" //// "_" - ["/" bundle] - ["/[1]" // "_" - ["[0]" extension] - [generation - [extension {"+" Nullary Unary Binary Trinary - nullary unary binary trinary}] - ["[0]" reference] - ["//" r "_" - ["[1][0]" runtime {"+" Operation Phase Handler Bundle Generator}] - ["[1][0]" case]]] - [// - ["[0]" synthesis {"+" %synthesis}] - ["[0]" generation] - [/// - ["[1]" phase]]]]]) + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" function] + ["[0]" try] + ["<>" parser + ["<s>" synthesis {"+" Parser}]]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" dictionary] + ["[0]" set] + ["[0]" list ("[1]#[0]" functor mix)]]] + [math + [number + ["f" frac]]] + ["@" target + ["_" r {"+" Expression}]]]] + ["[0]" //// "_" + ["/" bundle] + ["/[1]" // "_" + ["[0]" extension] + [generation + [extension {"+" Nullary Unary Binary Trinary + nullary unary binary trinary}] + ["[0]" reference] + ["//" r "_" + ["[1][0]" runtime {"+" Operation Phase Handler Bundle Generator}] + ["[1][0]" case]]] + [// + ["[0]" synthesis {"+" %synthesis}] + ["[0]" generation] + [/// + ["[1]" phase]]]]]) (def: .public (custom [parser handler]) (All (_ s) @@ -67,7 +67,7 @@ ... ... [@input (# ! each _.var (generation.symbol "input")) ... ... inputG (phase archive input) ... ... elseG (phase archive else) -... ... conditionalsG (: (Operation (List [Expression Expression])) +... ... conditionalsG (is (Operation (List [Expression Expression])) ... ... (monad.each ! (function (_ [chars branch]) ... ... (do ! ... ... [branchG (phase archive branch)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux index 7f71e4292..37a202c9f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/common.lux @@ -63,8 +63,8 @@ {synthesis.#Extension "lux syntax char case!" parameters} (do /////.monad [body (expression archive synthesis)] - (in (:as Statement - body))) + (in (as Statement + body))) (^.template [<tag>] [(pattern (<tag> value)) @@ -113,19 +113,19 @@ [inputG (phase archive input) else! (statement phase archive else) @input (# ! each _.local (generation.symbol "input")) - conditionals! (: (Operation (List [Expression Statement])) - (monad.each ! (function (_ [chars branch]) - (do ! - [branch! (statement phase archive branch)] - (in [(|> chars - (list#each (|>> .int _.int (_.= @input))) - (list#mix (function (_ clause total) - (if (same? _.nil total) - clause - (_.or clause total))) - _.nil)) - branch!]))) - conditionals)) + conditionals! (is (Operation (List [Expression Statement])) + (monad.each ! (function (_ [chars branch]) + (do ! + [branch! (statement phase archive branch)] + (in [(|> chars + (list#each (|>> .int _.int (_.= @input))) + (list#mix (function (_ clause total) + (if (same? _.nil total) + clause + (_.or clause total))) + _.nil)) + branch!]))) + conditionals)) ... .let [closure (_.lambda {.#None} (list @input) ... (list#mix (function (_ [test then] else) ... (_.if test (_.return then) else)) @@ -133,8 +133,8 @@ ... conditionals!))] ] ... (in (_.apply_lambda/* (list inputG) closure)) - (in (<| (:as Expression) - (: Statement) + (in (<| (as Expression) + (is Statement) ($_ _.then (_.set (list @input) inputG) (list#mix (function (_ [test then!] else!) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux index e11fc7aa6..53b71239f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/ruby/host.lux @@ -1,41 +1,41 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" function] - ["<>" parser - ["<s>" synthesis {"+" Parser}]]] - [data - [collection - ["[0]" dictionary] - ["[0]" list]] - [text - ["%" format {"+" format}]]] - [target - ["_" ruby {"+" Var Expression}]]]] - ["[0]" // "_" - ["[1][0]" common {"+" custom}] - ["//[1]" /// "_" - ["/" bundle] + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" function] + ["<>" parser + ["<s>" synthesis {"+" Parser}]]] + [data + [collection + ["[0]" dictionary] + ["[0]" list]] + [text + ["%" format {"+" format}]]] + [target + ["_" ruby {"+" Var Expression}]]]] + ["[0]" // "_" + ["[1][0]" common {"+" custom}] + ["//[1]" /// "_" + ["/" bundle] + ["/[1]" // "_" + ["[0]" extension] + [generation + [extension {"+" Nullary Unary Binary Trinary + nullary unary binary trinary}] + ["[0]" reference] + ["//" ruby "_" + ["[1][0]" runtime {"+" Operation Phase Handler Bundle + with_vars}]]] ["/[1]" // "_" - ["[0]" extension] - [generation - [extension {"+" Nullary Unary Binary Trinary - nullary unary binary trinary}] - ["[0]" reference] - ["//" ruby "_" - ["[1][0]" runtime {"+" Operation Phase Handler Bundle - with_vars}]]] - ["/[1]" // "_" - ["[0]" generation] - ["//[1]" /// "_" - ["[1][0]" phase]]]]]]) + ["[0]" generation] + ["//[1]" /// "_" + ["[1][0]" phase]]]]]]) (def: (array::new [size]) (Unary Expression) - (_.do "new" (list size) {.#None} (: _.CVar (_.manual "Array")))) + (_.do "new" (list size) {.#None} (is _.CVar (_.manual "Array")))) (def: array::length (Unary Expression) @@ -104,7 +104,7 @@ (custom [<s>.text (function (_ extension phase archive name) - (# ////////phase.monad in (: _.CVar (_.manual name))))])) + (# ////////phase.monad in (is _.CVar (_.manual name))))])) (def: ruby::apply (custom diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux index d55e5056a..6aa4e52b1 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/generation/scheme/common.lux @@ -1,42 +1,42 @@ (.using - [library - [lux "*" - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" function] - ["[0]" try] - ["<>" parser - ["<s>" synthesis {"+" Parser}]]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" dictionary] - ["[0]" set] - ["[0]" list ("[1]#[0]" functor mix)]]] - [math - [number - ["f" frac]]] - ["@" target - ["_" scheme {"+" Expression}]]]] - ["[0]" //// "_" - ["/" bundle] - ["/[1]" // "_" - ["[0]" extension] - [generation - [extension {"+" Nullary Unary Binary Trinary - nullary unary binary trinary}] - ["[0]" reference] - ["//" scheme "_" - ["[1][0]" runtime {"+" Operation Phase Handler Bundle Generator}] - ["[1][0]" case]]] - [// - ["[0]" synthesis {"+" %synthesis}] - ["[0]" generation] - [/// - ["[1]" phase]]]]]) + [library + [lux "*" + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" function] + ["[0]" try] + ["<>" parser + ["<s>" synthesis {"+" Parser}]]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" dictionary] + ["[0]" set] + ["[0]" list ("[1]#[0]" functor mix)]]] + [math + [number + ["f" frac]]] + ["@" target + ["_" scheme {"+" Expression}]]]] + ["[0]" //// "_" + ["/" bundle] + ["/[1]" // "_" + ["[0]" extension] + [generation + [extension {"+" Nullary Unary Binary Trinary + nullary unary binary trinary}] + ["[0]" reference] + ["//" scheme "_" + ["[1][0]" runtime {"+" Operation Phase Handler Bundle Generator}] + ["[1][0]" case]]] + [// + ["[0]" synthesis {"+" %synthesis}] + ["[0]" generation] + [/// + ["[1]" phase]]]]]) (def: .public (custom [parser handler]) (All (_ s) @@ -67,13 +67,13 @@ [@input (# ! each _.var (generation.symbol "input")) inputG (phase archive input) elseG (phase archive else) - conditionalsG (: (Operation (List [Expression Expression])) - (monad.each ! (function (_ [chars branch]) - (do ! - [branchG (phase archive branch)] - (in [(|> chars (list#each (|>> .int _.int (_.=/2 @input))) _.or) - branchG]))) - conditionals))] + conditionalsG (is (Operation (List [Expression Expression])) + (monad.each ! (function (_ [chars branch]) + (do ! + [branchG (phase archive branch)] + (in [(|> chars (list#each (|>> .int _.int (_.=/2 @input))) _.or) + branchG]))) + conditionals))] (in (_.let (list [@input inputG]) (list#mix (function (_ [test then] else) (_.if test then else)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux index 60b9cd96e..fbad56663 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/case.lux @@ -39,11 +39,11 @@ (def: .public register (-> Register Var/1) - (|>> (///reference.local //reference.system) :expected)) + (|>> (///reference.local //reference.system) as_expected)) (def: .public capture (-> Register Var/1) - (|>> (///reference.foreign //reference.system) :expected)) + (|>> (///reference.foreign //reference.system) as_expected)) (def: .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux index 2d18193e7..d91f824ad 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/common_lisp/function.lux @@ -1,33 +1,33 @@ (.using - [library - [lux {"-" function} - [abstract - ["[0]" monad {"+" do}]] - [control - pipe] - [data - ["[0]" product] - [text - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [target - ["_" common_lisp {"+" Expression Var/1}]]]] - ["[0]" // "_" - ["[1][0]" runtime {"+" Operation Phase Generator}] + [library + [lux {"-" function} + [abstract + ["[0]" monad {"+" do}]] + [control + pipe] + [data + ["[0]" product] + [text + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [target + ["_" common_lisp {"+" Expression Var/1}]]]] + ["[0]" // "_" + ["[1][0]" runtime {"+" Operation Phase Generator}] + ["[1][0]" reference] + ["[1][0]" case] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" case] - ["/[1]" // "_" - ["[1][0]" reference] + ["//[1]" /// "_" + [analysis {"+" Variant Tuple Abstraction Application Analysis}] + [synthesis {"+" Synthesis}] + ["[1][0]" generation {"+" Context}] ["//[1]" /// "_" - [analysis {"+" Variant Tuple Abstraction Application Analysis}] - [synthesis {"+" Synthesis}] - ["[1][0]" generation {"+" Context}] - ["//[1]" /// "_" - [arity {"+" Arity}] - ["[1][0]" phase ("[1]#[0]" monad)] - [reference - [variable {"+" Register Variable}]]]]]]) + [arity {"+" Arity}] + ["[1][0]" phase ("[1]#[0]" monad)] + [reference + [variable {"+" Register Variable}]]]]]]) (def: .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) @@ -38,7 +38,7 @@ (def: capture (-> Register Var/1) - (|>> (///reference.foreign //reference.system) :expected)) + (|>> (///reference.foreign //reference.system) as_expected)) (def: (with_closure inits function_definition) (-> (List (Expression Any)) (Expression Any) (Operation (Expression Any))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux index cca5cda23..4c3e03ca3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/case.lux @@ -38,7 +38,7 @@ (def: .public register (-> Register Var) - (|>> (///reference.local //reference.system) :expected)) + (|>> (///reference.local //reference.system) as_expected)) (def: .public (exec expression archive [this that]) (Generator [Synthesis Synthesis]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux index a3fa9317d..26ac01808 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/js/function.lux @@ -42,7 +42,7 @@ (def: capture (-> Register Var) - (|>> (///reference.foreign //reference.system) :expected)) + (|>> (///reference.foreign //reference.system) as_expected)) (def: (with_closure @self inits body!) (-> Var (List Expression) Statement [Statement Expression]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux index 85e221b18..5caa9c817 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/debug.lux @@ -1,17 +1,17 @@ (.using - [library - [lux "*" - [abstract - [monad {"+" do}]] - [control - ["[0]" io {"+" IO}] - ["[0]" try {"+" Try}]] - [data - [binary {"+" Binary}] - [text - ["%" format {"+" format}]]] - [world - ["[0]" file {"+" File}]]]]) + [library + [lux "*" + [abstract + [monad {"+" do}]] + [control + ["[0]" io {"+" IO}] + ["[0]" try {"+" Try}]] + [data + [binary {"+" Binary}] + [text + ["%" format {"+" format}]]] + [world + ["[0]" file {"+" File}]]]]) (def: extension ".class") @@ -20,8 +20,8 @@ (let [file_path (format name ..extension)] (do io.monad [outcome (do (try.with @) - [file (: (IO (Try (File IO))) - (file.get_file io.monad file.default file_path))] + [file (is (IO (Try (File IO))) + (file.get_file io.monad file.default file_path))] (# file over_write bytecode))] (in (case outcome {try.#Success definition} diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux index 1a0569fbc..7fd639b8f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function.lux @@ -73,19 +73,19 @@ (List (Resource Method)) (Bytecode Any)])) (let [classT (type.class class (list)) - fields (: (List (Resource Field)) - (list#composite (/foreign.variables environment) - (/partial.variables arity))) - methods (: (List (Resource Method)) - (list& (/init.method classT environment arity) - (/reset.method classT environment arity) - (if (arity.multiary? arity) - (|> (n.min arity /arity.maximum) - list.indices - (list#each (|>> ++ (/apply.method classT environment arity @begin body))) - (list& (/implementation.method classT arity @begin body))) - (list (/implementation.method classT arity @begin body) - (/apply.method classT environment arity @begin body 1)))))] + fields (is (List (Resource Field)) + (list#composite (/foreign.variables environment) + (/partial.variables arity))) + methods (is (List (Resource Method)) + (list& (/init.method classT environment arity) + (/reset.method classT environment arity) + (if (arity.multiary? arity) + (|> (n.min arity /arity.maximum) + list.indices + (list#each (|>> ++ (/apply.method classT environment arity @begin body))) + (list& (/implementation.method classT arity @begin body))) + (list (/implementation.method classT arity @begin body) + (/apply.method classT environment arity @begin body 1)))))] (do phase.monad [instance (/new.instance generate archive classT environment arity)] (in [fields methods instance])))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux index 14d2fdc03..e6734dfcb 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux @@ -87,12 +87,12 @@ (def: .public (method class environment arity) (-> (Type Class) (Environment Synthesis) Arity (Resource Method)) (let [environment_size (list.size environment) - offset_foreign (: (-> Register Register) - (n.+ 1)) - offset_arity (: (-> Register Register) - (|>> offset_foreign (n.+ environment_size))) - offset_partial (: (-> Register Register) - (|>> offset_arity (n.+ 1)))] + offset_foreign (is (-> Register Register) + (n.+ 1)) + offset_arity (is (-> Register Register) + (|>> offset_foreign (n.+ environment_size))) + offset_partial (is (-> Register Register) + (|>> offset_arity (n.+ 1)))] (method.method //.modifier ..name #0 (..type environment arity) (list) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux index 3edbe1e05..5087f0357 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/new.lux @@ -60,13 +60,13 @@ (def: .public (method class environment arity) (-> (Type Class) (Environment Synthesis) Arity (Resource Method)) - (let [after_this (: (-> Nat Nat) - (n.+ 1)) + (let [after_this (is (-> Nat Nat) + (n.+ 1)) environment_size (list.size environment) - after_environment (: (-> Nat Nat) - (|>> after_this (n.+ environment_size))) - after_arity (: (-> Nat Nat) - (|>> after_environment (n.+ 1)))] + after_environment (is (-> Nat Nat) + (|>> after_this (n.+ environment_size))) + after_arity (is (-> Nat Nat) + (|>> after_environment (n.+ 1)))] (method.method //.modifier //init.name #0 (//init.type environment arity) (list) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux index ced3ea64a..d512d7050 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/host.lux @@ -147,7 +147,7 @@ (# io.monad each (function (_ library) (dictionary.key? library class_name))) (try.lifted io.monad) - (: (IO (Try Bit)))) + (is (IO (Try Bit)))) _ (if existing_class? (in []) (loader.store class_name class_bytecode library))] @@ -166,30 +166,30 @@ (io (let [library (loader.new_library []) loader (loader.memory library)] [loader - (: //runtime.Host - (implementation - (def: (evaluate context @it,valueG) - (# try.monad each product.left - (..evaluate! library loader (format "E" (//runtime.class_name context)) @it,valueG))) - - (def: execute - (..execute! library loader)) - - (def: define - (..define! library loader)) - - (def: (ingest context bytecode) - [(//runtime.class_name context) bytecode]) - - (def: (re_learn context custom [_ bytecode]) - (io.run! (loader.store (maybe.else (//runtime.class_name context) custom) bytecode library))) - - (def: (re_load context custom [directive_name bytecode]) - (io.run! - (do (try.with io.monad) - [.let [class_name (maybe.else (//runtime.class_name context) - custom)] - _ (loader.store class_name bytecode library) - class (loader.load class_name loader)] - (# io.monad in (..class_value class_name class))))) - ))]))) + (is //runtime.Host + (implementation + (def: (evaluate context @it,valueG) + (# try.monad each product.left + (..evaluate! library loader (format "E" (//runtime.class_name context)) @it,valueG))) + + (def: execute + (..execute! library loader)) + + (def: define + (..define! library loader)) + + (def: (ingest context bytecode) + [(//runtime.class_name context) bytecode]) + + (def: (re_learn context custom [_ bytecode]) + (io.run! (loader.store (maybe.else (//runtime.class_name context) custom) bytecode library))) + + (def: (re_load context custom [directive_name bytecode]) + (io.run! + (do (try.with io.monad) + [.let [class_name (maybe.else (//runtime.class_name context) + custom)] + _ (loader.store class_name bytecode library) + class (loader.load class_name loader)] + (# io.monad in (..class_value class_name class))))) + ))]))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux index 10f11edd9..21a10ad06 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/primitive.lux @@ -122,7 +122,7 @@ _ (let [constantI (if (i.= ..d0_bits - (java/lang/Double::doubleToRawLongBits (:as java/lang/Double value))) + (java/lang/Double::doubleToRawLongBits (as java/lang/Double value))) _.dconst_0 (_.double value))] (do _.monad diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux index 23ec9402e..2b761e907 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/program.lux @@ -92,16 +92,16 @@ _.iconst_2 (_.anewarray ^Object) ) - set_side! (: (-> (Bytecode Any) (Bytecode Any)) - (function (_ index) - ($_ _.composite - ... ?P - _.dup_x1 ... P?P - _.swap ... PP? - index ... PP?I - _.swap ... PPI? - _.aastore ... P - )))] + set_side! (is (-> (Bytecode Any) (Bytecode Any)) + (function (_ index) + ($_ _.composite + ... ?P + _.dup_x1 ... P?P + _.swap ... PP? + index ... PP?I + _.swap ... PPI? + _.aastore ... P + )))] ($_ _.composite ... RL empty_pair ... RLP diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux index 6031ed1db..789884c63 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/runtime.lux @@ -337,13 +337,13 @@ _.isub (_.int (i32.i32 (.i64 +1))) _.isub) - again (: (-> Label (Bytecode Any)) - (function (_ @) - ($_ _.composite - ... lefts, sumT - update_$variant ... lefts, sumT - update_$lefts ... sub_lefts - (_.goto @))))]] + again (is (-> Label (Bytecode Any)) + (function (_ @) + ($_ _.composite + ... lefts, sumT + update_$variant ... lefts, sumT + update_$lefts ... sub_lefts + (_.goto @))))]] ($_ _.composite $lefts (_.set_label @loop) @@ -399,12 +399,12 @@ update_$tuple ($_ _.composite $tuple $last_right _.aaload (_.checkcast //type.tuple) _.astore_0) - recur (: (-> Label (Bytecode Any)) - (function (_ @loop) - ($_ _.composite - update_$lefts - update_$tuple - (_.goto @loop)))) + recur (is (-> Label (Bytecode Any)) + (function (_ @loop) + ($_ _.composite + update_$lefts + update_$tuple + (_.goto @loop)))) left_projection::method (method.method ..modifier ..left_projection::name @@ -542,10 +542,10 @@ (def: generate_runtime (Operation [artifact.ID (Maybe Text) Binary]) (let [class (..reflection ..class) - modifier (: (Modifier Class) - ($_ modifier#composite - class.public - class.final)) + modifier (is (Modifier Class) + ($_ modifier#composite + class.public + class.final)) bytecode (<| (format.result class.writer) try.trusted (class.class jvm/version.v6_0 @@ -609,16 +609,16 @@ $partials (_.putfield //function.class //function/count.field //function/count.type) _.return))}) - modifier (: (Modifier Class) - ($_ modifier#composite - class.public - class.abstract)) + modifier (is (Modifier Class) + ($_ modifier#composite + class.public + class.abstract)) class (..reflection //function.class) - partial_count (: (Resource Field) - (field.field (modifier#composite field.public field.final) - //function/count.field - #0 //function/count.type - sequence.empty)) + partial_count (is (Resource Field) + (field.field (modifier#composite field.public field.final) + //function/count.field + #0 //function/count.type + sequence.empty)) bytecode (<| (format.result class.writer) try.trusted (class.class jvm/version.v6_0 diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux index 6d79e0750..2c35a85bd 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/case.lux @@ -36,11 +36,11 @@ (def: .public register (-> Register Var) - (|>> (///reference.local //reference.system) :expected)) + (|>> (///reference.local //reference.system) as_expected)) (def: .public capture (-> Register Var) - (|>> (///reference.foreign //reference.system) :expected)) + (|>> (///reference.foreign //reference.system) as_expected)) (def: .public (exec expression archive [this that]) (Generator [Synthesis Synthesis]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux index ef4118721..bc3e2210d 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/function.lux @@ -44,7 +44,7 @@ (def: capture (-> Register Var) - (|>> (///reference.foreign //reference.system) :expected)) + (|>> (///reference.foreign //reference.system) as_expected)) (def: (with_closure inits @self @args body!) (-> (List Expression) Var (List Var) Statement [Statement Expression]) @@ -93,9 +93,9 @@ initialize_self! (list.indices arity)) pack (|>> (list) _.array) - unpack (: (-> Expression Expression) - (.function (_ it) - (_.apply (list it) (_.var "table.unpack")))) + unpack (is (-> Expression Expression) + (.function (_ it) + (_.apply (list it) (_.var "table.unpack")))) @var_args (_.var "...")] .let [[definition instantiation] (with_closure closureO+ @self (list @var_args) ($_ _.then diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux index 9409ab00f..57e35ab75 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/lua/loop.lux @@ -91,26 +91,26 @@ locals (|> initsO+ list.enumeration (list#each (|>> product.left (n.+ start) //case.register))) - [directive instantiation] (: [Statement Expression] - (case (|> (synthesis.path/then bodyS) - //case.dependencies - (set.of_list _.hash) - (set.difference (set.of_list _.hash locals)) - set.list) - {.#End} - [(_.function @loop locals - scope!) - @loop] + [directive instantiation] (is [Statement Expression] + (case (|> (synthesis.path/then bodyS) + //case.dependencies + (set.of_list _.hash) + (set.difference (set.of_list _.hash locals)) + set.list) + {.#End} + [(_.function @loop locals + scope!) + @loop] - foreigns - (let [@context (_.var (format (_.code @loop) "_context"))] - [(_.function @context foreigns - ($_ _.then - (<| (_.local_function @loop locals) - scope!) - (_.return @loop) - )) - (_.apply foreigns @context)])))] + foreigns + (let [@context (_.var (format (_.code @loop) "_context"))] + [(_.function @context foreigns + ($_ _.then + (<| (_.local_function @loop locals) + scope!) + (_.return @loop) + )) + (_.apply foreigns @context)])))] _ (/////generation.execute! directive) _ (/////generation.save! artifact_id {.#None} directive)] (in (_.apply initsO+ instantiation))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux index 595c313cf..761b34fab 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/case.lux @@ -38,11 +38,11 @@ (def: .public register (-> Register Var) - (|>> (///reference.local //reference.system) :expected)) + (|>> (///reference.local //reference.system) as_expected)) (def: .public capture (-> Register Var) - (|>> (///reference.foreign //reference.system) :expected)) + (|>> (///reference.foreign //reference.system) as_expected)) (def: .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux index add7ae3e5..bd95510e2 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/function.lux @@ -1,33 +1,33 @@ (.using - [library - [lux {"-" Global function} - [abstract - ["[0]" monad {"+" do}]] - [control - pipe] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor mix)]]] - [target - ["_" php {"+" Var Global Expression Argument Label Statement}]]]] - ["[0]" // "_" - ["[1][0]" runtime {"+" Operation Phase Phase! Generator}] + [library + [lux {"-" Global function} + [abstract + ["[0]" monad {"+" do}]] + [control + pipe] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor mix)]]] + [target + ["_" php {"+" Var Global Expression Argument Label Statement}]]]] + ["[0]" // "_" + ["[1][0]" runtime {"+" Operation Phase Phase! Generator}] + ["[1][0]" reference] + ["[1][0]" case] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" case] - ["/[1]" // "_" - ["[1][0]" reference] + ["//[1]" /// "_" + [analysis {"+" Variant Tuple Abstraction Application Analysis}] + [synthesis {"+" Synthesis}] + ["[1][0]" generation {"+" Context}] ["//[1]" /// "_" - [analysis {"+" Variant Tuple Abstraction Application Analysis}] - [synthesis {"+" Synthesis}] - ["[1][0]" generation {"+" Context}] - ["//[1]" /// "_" - [arity {"+" Arity}] - ["[1][0]" phase ("[1]#[0]" monad)] - [reference - [variable {"+" Register Variable}]]]]]]) + [arity {"+" Arity}] + ["[1][0]" phase ("[1]#[0]" monad)] + [reference + [variable {"+" Register Variable}]]]]]]) (def: .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) @@ -38,7 +38,7 @@ (def: capture (-> Register Var) - (|>> (///reference.foreign //reference.system) :expected)) + (|>> (///reference.foreign //reference.system) as_expected)) (def: input (|>> ++ //case.register)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux index 7fc0e8c4d..1f2d6253c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/php/loop.lux @@ -1,37 +1,37 @@ (.using - [library - [lux {"-" Scope} - [abstract - ["[0]" monad {"+" do}]] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor mix)] - ["[0]" set {"+" Set}]]] - [math - [number - ["n" nat]]] - [target - ["_" php {"+" Var Expression Label Statement}]]]] - ["[0]" // "_" - [runtime {"+" Operation Phase Phase! Generator Generator!}] - ["[1][0]" case] + [library + [lux {"-" Scope} + [abstract + ["[0]" monad {"+" do}]] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor mix)] + ["[0]" set {"+" Set}]]] + [math + [number + ["n" nat]]] + [target + ["_" php {"+" Var Expression Label Statement}]]]] + ["[0]" // "_" + [runtime {"+" Operation Phase Phase! Generator Generator!}] + ["[1][0]" case] + ["/[1]" // "_" + ["[1][0]" reference] ["/[1]" // "_" - ["[1][0]" reference] + [synthesis + ["[0]" case]] ["/[1]" // "_" - [synthesis - ["[0]" case]] - ["/[1]" // "_" - ["[0]"synthesis {"+" Scope Synthesis}] - ["[1][0]" generation] - ["//[1]" /// "_" - ["[1][0]" phase] - [meta - [archive {"+" Archive}]] - [reference - [variable {"+" Register}]]]]]]]) + ["[0]"synthesis {"+" Scope Synthesis}] + ["[1][0]" generation] + ["//[1]" /// "_" + ["[1][0]" phase] + [meta + [archive {"+" Archive}]] + [reference + [variable {"+" Register}]]]]]]]) (def: @scope (-> Nat Label) @@ -84,23 +84,23 @@ (list#each (|>> product.left (n.+ start) //case.register _.parameter))) @loop (_.constant (///reference.artifact [loop_module loop_artifact])) loop_variables (set.of_list _.hash (list#each product.right locals)) - referenced_variables (: (-> Synthesis (Set Var)) - (|>> synthesis.path/then - //case.dependencies - (set.of_list _.hash))) - [directive instantiation] (: [Statement Expression] - (case (|> (list#each referenced_variables initsS+) - (list#mix set.union (referenced_variables bodyS)) - (set.difference loop_variables) - set.list) - {.#End} - [(_.define_function @loop (list) scope!) - @loop] + referenced_variables (is (-> Synthesis (Set Var)) + (|>> synthesis.path/then + //case.dependencies + (set.of_list _.hash))) + [directive instantiation] (is [Statement Expression] + (case (|> (list#each referenced_variables initsS+) + (list#mix set.union (referenced_variables bodyS)) + (set.difference loop_variables) + set.list) + {.#End} + [(_.define_function @loop (list) scope!) + @loop] - foreigns - [(<| (_.define_function @loop (list#each _.parameter foreigns)) - (_.return (_.closure (list#each _.parameter foreigns) (list) scope!))) - (_.apply/* foreigns @loop)]))] + foreigns + [(<| (_.define_function @loop (list#each _.parameter foreigns)) + (_.return (_.closure (list#each _.parameter foreigns) (list) scope!))) + (_.apply/* foreigns @loop)]))] _ (/////generation.execute! directive) _ (/////generation.save! loop_artifact directive)] (in (_.apply/* (list) instantiation))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux index 3e4699361..aed266e9f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/case.lux @@ -48,11 +48,11 @@ (def: .public register (-> Register SVar) - (|>> (///reference.local //reference.system) :expected)) + (|>> (///reference.local //reference.system) as_expected)) (def: .public capture (-> Register SVar) - (|>> (///reference.foreign //reference.system) :expected)) + (|>> (///reference.foreign //reference.system) as_expected)) (def: .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux index 9692d6ee7..efbefac6b 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/function.lux @@ -43,7 +43,7 @@ (def: .public capture (-> Register SVar) - (|>> (///reference.foreign //reference.system) :expected)) + (|>> (///reference.foreign //reference.system) as_expected)) (def: (with_closure function_id @function inits function_definition) (-> artifact.ID SVar (List (Expression Any)) (Statement Any) (Operation (Expression Any))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux index 36762f8cc..5c6d545f1 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/python/loop.lux @@ -89,23 +89,23 @@ actual_loop (<| (_.def @loop locals) ..set_scope body!) - [directive instantiation] (: [(Statement Any) (Expression Any)] - (case (|> (synthesis.path/then bodyS) - //case.dependencies - (set.of_list _.hash) - (set.difference (set.of_list _.hash locals)) - set.list) - {.#End} - [actual_loop - @loop] + [directive instantiation] (is [(Statement Any) (Expression Any)] + (case (|> (synthesis.path/then bodyS) + //case.dependencies + (set.of_list _.hash) + (set.difference (set.of_list _.hash locals)) + set.list) + {.#End} + [actual_loop + @loop] - foreigns - [(_.def @loop foreigns - ($_ _.then - actual_loop - (_.return @loop) - )) - (_.apply/* foreigns @loop)]))] + foreigns + [(_.def @loop foreigns + ($_ _.then + actual_loop + (_.return @loop) + )) + (_.apply/* foreigns @loop)]))] _ (/////generation.execute! directive) _ (/////generation.save! loop_artifact {.#None} directive)] (in (_.apply/* initsO+ instantiation))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux index 2b849271b..d75170250 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/case.lux @@ -39,11 +39,11 @@ (def: .public register (-> Register SVar) - (|>> (///reference.local //reference.system) :expected)) + (|>> (///reference.local //reference.system) as_expected)) (def: .public capture (-> Register SVar) - (|>> (///reference.foreign //reference.system) :expected)) + (|>> (///reference.foreign //reference.system) as_expected)) (def: .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux index 8a56bf21a..6968c5618 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/runtime.lux @@ -1,45 +1,45 @@ (.using - [library - [lux {"-" Location ++ i64} - ["[0]" meta] - [abstract - ["[0]" monad {"+" do}]] - [control - ["[0]" function] - ["<>" parser - ["<[0]>" code]]] - [data - ["[0]" product] - ["[0]" text ("[1]#[0]" hash) - ["%" format {"+" format}] - [encoding - ["[0]" utf8]]] - [collection - ["[0]" list ("[1]#[0]" functor)] - ["[0]" sequence]]] - ["[0]" macro - [syntax {"+" syntax:}] - ["[0]" code]] - [math - [number {"+" hex} - ["n" nat] - ["i" int ("[1]#[0]" interval)] - ["[0]" i64]]] - ["@" target - ["_" r {"+" SVar Expression}]]]] - ["[0]" /// "_" - ["[1][0]" reference] - ["//[1]" /// "_" - [analysis {"+" Variant}] - ["[1][0]" synthesis {"+" Synthesis}] - ["[1][0]" generation] - ["//[1]" /// - ["[1][0]" phase] - [reference - [variable {"+" Register}]] - [meta - [archive {"+" Output Archive} - ["[0]" artifact {"+" Registry}]]]]]]) + [library + [lux {"-" Location ++ i64} + ["[0]" meta] + [abstract + ["[0]" monad {"+" do}]] + [control + ["[0]" function] + ["<>" parser + ["<[0]>" code]]] + [data + ["[0]" product] + ["[0]" text ("[1]#[0]" hash) + ["%" format {"+" format}] + [encoding + ["[0]" utf8]]] + [collection + ["[0]" list ("[1]#[0]" functor)] + ["[0]" sequence]]] + ["[0]" macro + [syntax {"+" syntax:}] + ["[0]" code]] + [math + [number {"+" hex} + ["n" nat] + ["i" int ("[1]#[0]" interval)] + ["[0]" i64]]] + ["@" target + ["_" r {"+" SVar Expression}]]]] + ["[0]" /// "_" + ["[1][0]" reference] + ["//[1]" /// "_" + [analysis {"+" Variant}] + ["[1][0]" synthesis {"+" Synthesis}] + ["[1][0]" generation] + ["//[1]" /// + ["[1][0]" phase] + [reference + [variable {"+" Register}]] + [meta + [archive {"+" Output Archive} + ["[0]" artifact {"+" Registry}]]]]]]) (def: module_id 0) @@ -271,11 +271,11 @@ (_.apply (list value) (_.var "is.na"))) isTRUE? (function (_ value) (_.apply (list value) (_.var "isTRUE"))) - comparison (: (-> (-> Expression Expression) Expression) - (function (_ field) - (|> (|> (field sample) (_.= (field reference))) - (_.or (|> (n/a? (field sample)) - (_.and (n/a? (field reference))))))))] + comparison (is (-> (-> Expression Expression) Expression) + (function (_ field) + (|> (|> (field sample) (_.= (field reference))) + (_.or (|> (n/a? (field sample)) + (_.and (n/a? (field reference))))))))] (|> (comparison i64_high) (_.and (comparison i64_low)) isTRUE?))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux index 50fae65d9..79ed4680c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/reference.lux @@ -55,10 +55,10 @@ (type: .public (System expression) (Interface - (: (-> Text expression) - constant') - (: (-> Text expression) - variable'))) + (is (-> Text expression) + constant') + (is (-> Text expression) + variable'))) (def: .public (constant system archive name) (All (_ anchor expression directive) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux index 1d513b57b..284fa79c6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/case.lux @@ -46,11 +46,11 @@ (def: .public register (-> Register LVar) - (|>> (///reference.local //reference.system) :expected)) + (|>> (///reference.local //reference.system) as_expected)) (def: .public capture (-> Register LVar) - (|>> (///reference.foreign //reference.system) :expected)) + (|>> (///reference.foreign //reference.system) as_expected)) (def: .public (exec expression archive [this that]) (Generator [Synthesis Synthesis]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux index 6d4193788..f6b20a5d6 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux @@ -41,7 +41,7 @@ (def: .public capture (-> Register LVar) - (|>> (///reference.foreign //reference.system) :expected)) + (|>> (///reference.foreign //reference.system) as_expected)) (def: (with_closure inits self function_definition) (-> (List Expression) Text Expression [Statement Expression]) @@ -77,13 +77,13 @@ arityO (|> arity .int _.int) limitO (|> arity -- .int _.int) @num_args (_.local "num_args") - @self (: _.Location - (case closureO+ - {.#End} - (_.global function_name) + @self (is _.Location + (case closureO+ + {.#End} + (_.global function_name) - _ - (_.local function_name))) + _ + (_.local function_name))) initialize_self! (_.set (list (//case.register 0)) @self) initialize! (list#mix (.function (_ post pre!) ($_ _.then diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux index aeed6ea59..e5cc0a650 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/case.lux @@ -39,11 +39,11 @@ (def: .public register (-> Register Var) - (|>> (///reference.local //reference.system) :expected)) + (|>> (///reference.local //reference.system) as_expected)) (def: .public capture (-> Register Var) - (|>> (///reference.foreign //reference.system) :expected)) + (|>> (///reference.foreign //reference.system) as_expected)) (def: .public (let expression archive [valueS register bodyS]) (Generator [Synthesis Register Synthesis]) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux index 2c5cf5a82..9ff5b8f94 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/scheme/function.lux @@ -1,33 +1,33 @@ (.using - [library - [lux {"-" function} - [abstract - ["[0]" monad {"+" do}]] - [control - pipe] - [data - ["[0]" product] - ["[0]" text - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [target - ["_" scheme {"+" Expression Computation Var}]]]] - ["[0]" // "_" - ["[1][0]" runtime {"+" Operation Phase Generator}] + [library + [lux {"-" function} + [abstract + ["[0]" monad {"+" do}]] + [control + pipe] + [data + ["[0]" product] + ["[0]" text + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [target + ["_" scheme {"+" Expression Computation Var}]]]] + ["[0]" // "_" + ["[1][0]" runtime {"+" Operation Phase Generator}] + ["[1][0]" reference] + ["[1][0]" case] + ["/[1]" // "_" ["[1][0]" reference] - ["[1][0]" case] - ["/[1]" // "_" - ["[1][0]" reference] + ["//[1]" /// "_" + [analysis {"+" Variant Tuple Abstraction Application Analysis}] + [synthesis {"+" Synthesis}] + ["[1][0]" generation {"+" Context}] ["//[1]" /// "_" - [analysis {"+" Variant Tuple Abstraction Application Analysis}] - [synthesis {"+" Synthesis}] - ["[1][0]" generation {"+" Context}] - ["//[1]" /// "_" - [arity {"+" Arity}] - ["[1][0]" phase ("[1]#[0]" monad)] - [reference - [variable {"+" Register Variable}]]]]]]) + [arity {"+" Arity}] + ["[1][0]" phase ("[1]#[0]" monad)] + [reference + [variable {"+" Register Variable}]]]]]]) (def: .public (apply expression archive [functionS argsS+]) (Generator (Application Synthesis)) @@ -38,7 +38,7 @@ (def: capture (-> Register Var) - (|>> (///reference.foreign //reference.system) :expected)) + (|>> (///reference.foreign //reference.system) as_expected)) (def: (with_closure inits function_definition) (-> (List Expression) Computation (Operation Computation)) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux index 13d591126..87abcaff0 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/function.lux @@ -65,17 +65,17 @@ [locals /.locals] (in (|> functionS (//loop.optimization true locals argsS) - (maybe#each (: (-> [Nat (List Synthesis) Synthesis] Synthesis) - (function (_ [start inits iteration]) - (case iteration - (pattern (/.loop/scope [start' inits' output])) - (if (and (n.= start start') - (list.empty? inits')) - (/.loop/scope [start inits output]) - (/.loop/scope [start inits iteration])) + (maybe#each (is (-> [Nat (List Synthesis) Synthesis] Synthesis) + (function (_ [start inits iteration]) + (case iteration + (pattern (/.loop/scope [start' inits' output])) + (if (and (n.= start start') + (list.empty? inits')) + (/.loop/scope [start inits output]) + (/.loop/scope [start inits iteration])) - _ - (/.loop/scope [start inits iteration]))))) + _ + (/.loop/scope [start inits iteration]))))) (maybe.else <apply>)))) (in <apply>)) @@ -261,20 +261,20 @@ bodyS (/.with_currying? true (/.with_locals 2 (phase archive bodyA))) - abstraction (: (Operation Abstraction) - (case bodyS - (pattern (/.function/abstraction [env' down_arity' bodyS'])) - (|> bodyS' - (grow env') - (# ! each (function (_ body) - [/.#environment environment - /.#arity (++ down_arity') - /.#body body]))) - - _ - (in [/.#environment environment - /.#arity 1 - /.#body bodyS]))) + abstraction (is (Operation Abstraction) + (case bodyS + (pattern (/.function/abstraction [env' down_arity' bodyS'])) + (|> bodyS' + (grow env') + (# ! each (function (_ body) + [/.#environment environment + /.#arity (++ down_arity') + /.#body body]))) + + _ + (in [/.#environment environment + /.#arity 1 + /.#body bodyS]))) currying? /.currying?] (in (/.function/abstraction (if currying? diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux index 85e4d28af..5429a8f0c 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/synthesis/variable.lux @@ -278,11 +278,11 @@ [{<tag> [[test then] elses]} (do [! try.monad] [[redundancy then] (again [redundancy then]) - [redundancy elses] (..list_optimization (: (Optimization [<type> Path]) - (function (_ [redundancy [else_test else_then]]) - (do ! - [[redundancy else_then] (again [redundancy else_then])] - (in [redundancy [else_test else_then]])))) + [redundancy elses] (..list_optimization (is (Optimization [<type> Path]) + (function (_ [redundancy [else_test else_then]]) + (do ! + [[redundancy else_then] (again [redundancy else_then])] + (in [redundancy [else_test else_then]])))) [redundancy elses])] (in [redundancy {<tag> [[test then] elses]}]))]) ([/.#I64_Fork I64] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux index a2a47c775..dbe91632a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux @@ -186,8 +186,8 @@ (-> Source (Either [Source Text] [Source a]))) (template: (!with_char+ @source_code_size @source_code @offset @char @else @body) - [(if (!i/< (:as Int @source_code_size) - (:as Int @offset)) + [(if (!i/< (as Int @source_code_size) + (as Int @offset)) (let [@char ("lux text char" @offset @source_code)] @body) @else)]) @@ -202,7 +202,7 @@ ... {.#Left error} <<otherwise>> - (:expected <<otherwise>>))]) + (as_expected <<otherwise>>))]) (template: (!horizontal where offset source_code) [[(revised .#column ++ where) @@ -228,8 +228,8 @@ [(inline: (<name> parse where offset source_code) (-> (Parser Code) Location Offset Text (Either [Source Text] [Source Code])) - (loop [source (: Source [(!forward 1 where) offset source_code]) - stack (: (List Code) {.#End})] + (loop [source (is Source [(!forward 1 where) offset source_code]) + stack (is (List Code) {.#End})] (case (parse source) {.#Right [source' top]} (again source' {.#Item top stack}) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux index 3fd47f828..3b1a2ad84 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/synthesis.lux @@ -428,7 +428,7 @@ (# (list.equivalence (product.equivalence <equivalence> =)) = {.#Item reference_item} {.#Item sample_item})]) - ([#I64_Fork (: (Equivalence I64) i64.equivalence)] + ([#I64_Fork (is (Equivalence I64) i64.equivalence)] [#F64_Fork f.equivalence] [#Text_Fork text.equivalence]) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux index fbcb3c0f9..b1397ef8c 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux @@ -27,7 +27,7 @@ [number ["n" nat ("[1]#[0]" equivalence)]]] [type - abstract]]] + [abstract {"-" pattern}]]]] [/ ["[0]" artifact] ["[0]" registry {"+" Registry}] @@ -79,16 +79,16 @@ (def: next (-> Archive module.ID) - (|>> :representation (the #next))) + (|>> representation (the #next))) (def: .public empty Archive - (:abstraction [#next 0 - #resolver (dictionary.empty text.hash)])) + (abstraction [#next 0 + #resolver (dictionary.empty text.hash)])) (def: .public (id module archive) (-> descriptor.Module Archive (Try module.ID)) - (let [(open "/[0]") (:representation archive)] + (let [(open "/[0]") (representation archive)] (case (dictionary.value module /#resolver) {.#Some [id _]} {try.#Success id} @@ -99,7 +99,7 @@ (def: .public (reserve module archive) (-> descriptor.Module Archive (Try [module.ID Archive])) - (let [(open "/[0]") (:representation archive)] + (let [(open "/[0]") (representation archive)] (case (dictionary.value module /#resolver) {.#Some _} (exception.except ..module_has_already_been_reserved [module]) @@ -107,20 +107,20 @@ {.#None} {try.#Success [/#next (|> archive - :representation - (revised #resolver (dictionary.has module [/#next (: (Maybe (Entry Any)) {.#None})])) + representation + (revised #resolver (dictionary.has module [/#next (is (Maybe (Entry Any)) {.#None})])) (revised #next ++) - :abstraction)]}))) + abstraction)]}))) (def: .public (has module entry archive) (-> descriptor.Module (Entry Any) Archive (Try Archive)) - (let [(open "/[0]") (:representation archive)] + (let [(open "/[0]") (representation archive)] (case (dictionary.value module /#resolver) {.#Some [id {.#None}]} {try.#Success (|> archive - :representation + representation (revised ..#resolver (dictionary.has module [id {.#Some entry}])) - :abstraction)} + abstraction)} {.#Some [id {.#Some [existing_module existing_output existing_registry]}]} (if (same? (the module.#document existing_module) @@ -134,7 +134,7 @@ (def: .public entries (-> Archive (List [descriptor.Module [module.ID (Entry Any)]])) - (|>> :representation + (|>> representation (the #resolver) dictionary.entries (list.all (function (_ [module [module_id entry]]) @@ -142,7 +142,7 @@ (def: .public (find module archive) (-> descriptor.Module Archive (Try (Entry Any))) - (let [(open "/[0]") (:representation archive)] + (let [(open "/[0]") (representation archive)] (case (dictionary.value module /#resolver) {.#Some [id {.#Some entry}]} {try.#Success entry} @@ -164,7 +164,7 @@ (def: .public archived (-> Archive (List descriptor.Module)) - (|>> :representation + (|>> representation (the #resolver) dictionary.entries (list.all (function (_ [module [id descriptor+document]]) @@ -174,7 +174,7 @@ (def: .public (reserved? archive module) (-> Archive descriptor.Module Bit) - (let [(open "/[0]") (:representation archive)] + (let [(open "/[0]") (representation archive)] (case (dictionary.value module /#resolver) {.#Some [id _]} true @@ -184,13 +184,13 @@ (def: .public reserved (-> Archive (List descriptor.Module)) - (|>> :representation + (|>> representation (the #resolver) dictionary.keys)) (def: .public reservations (-> Archive (List [descriptor.Module module.ID])) - (|>> :representation + (|>> representation (the #resolver) dictionary.entries (list#each (function (_ [module [id _]]) @@ -198,9 +198,9 @@ (def: .public (merged additions archive) (-> Archive Archive Archive) - (let [[+next +resolver] (:representation additions)] + (let [[+next +resolver] (representation additions)] (|> archive - :representation + representation (revised #next (n.max +next)) (revised #resolver (function (_ resolver) (list#mix (function (_ [module [id entry]] resolver) @@ -212,7 +212,7 @@ resolver)) resolver (dictionary.entries +resolver)))) - :abstraction))) + abstraction))) (type: Reservation [descriptor.Module module.ID]) @@ -236,7 +236,7 @@ (def: .public (export version archive) (-> Version Archive Binary) - (let [(open "/[0]") (:representation archive)] + (let [(open "/[0]") (representation archive)] (|> /#resolver dictionary.entries (list.all (function (_ [module [id descriptor+document]]) @@ -258,10 +258,10 @@ [[actual next reservations] (<binary>.result ..reader binary) _ (exception.assertion ..version_mismatch [expected actual] (n#= expected actual))] - (in (:abstraction + (in (abstraction [#next next #resolver (list#mix (function (_ [module id] archive) - (dictionary.has module [id (: (Maybe (Entry Any)) {.#None})] archive)) - (the #resolver (:representation ..empty)) + (dictionary.has module [id (is (Maybe (Entry Any)) {.#None})] archive)) + (the #resolver (representation ..empty)) reservations)])))) ) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux index a124fae6a..7ae44b175 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/key.lux @@ -2,7 +2,7 @@ [library [lux "*" [type - abstract]]] + [abstract {"-" pattern}]]]] [// [signature {"+" Signature}]]) @@ -11,9 +11,9 @@ (def: .public signature (All (_ ?) (-> (Key ?) Signature)) - (|>> :representation)) + (|>> representation)) (def: .public (key signature sample) (All (_ d) (-> Signature d (Key d))) - (:abstraction signature)) + (abstraction signature)) ) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux index bc74b9c3c..73214b2ab 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/module/document.lux @@ -13,8 +13,8 @@ ["[0]" dictionary {"+" Dictionary}]] [format ["[0]" binary {"+" Writer}]]] - [type {"+" :sharing} - abstract]]] + [type {"+" sharing} + [abstract {"-" pattern}]]]] [/// ["[0]" signature {"+" Signature} ("[1]#[0]" equivalence)] ["[0]" key {"+" Key}]]) @@ -32,40 +32,40 @@ (def: .public (content key document) (All (_ d) (-> (Key d) (Document Any) (Try d))) - (let [[document//signature document//content] (:representation document)] + (let [[document//signature document//content] (representation document)] (if (# signature.equivalence = (key.signature key) document//signature) - {try.#Success (:sharing [e] - (Key e) - key - - e - (:expected document//content))} + {try.#Success (sharing [e] + (Key e) + key + + e + (as_expected document//content))} (exception.except ..invalid_signature [(key.signature key) document//signature])))) (def: .public (document key content) (All (_ d) (-> (Key d) d (Document d))) - (:abstraction [#signature (key.signature key) - #content content])) + (abstraction [#signature (key.signature key) + #content content])) (def: .public (marked? key document) (All (_ d) (-> (Key d) (Document Any) (Try (Document d)))) (do try.monad [_ (..content key document)] - (in (:expected document)))) + (in (as_expected document)))) (def: .public signature (-> (Document Any) Signature) - (|>> :representation (the #signature))) + (|>> representation (the #signature))) (def: .public (writer content) (All (_ d) (-> (Writer d) (Writer (Document d)))) (let [writer ($_ binary.and signature.writer content)] - (|>> :representation writer))) + (|>> representation writer))) (def: .public (parser key it) (All (_ d) (-> (Key d) (Parser d) (Parser (Document d)))) @@ -76,5 +76,5 @@ (in []) (<>.lifted (exception.except ..invalid_signature [expected actual]))) it it] - (in (:abstraction [actual it])))) + (in (abstraction [actual it])))) ) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux index d2921be2e..3e9726924 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/registry.lux @@ -23,7 +23,7 @@ [macro ["^" pattern]] [type - abstract]]] + [abstract {"-" pattern}]]]] ["[0]" // "_" ["[0]" unit] ["[1]" artifact {"+" Artifact ID} @@ -36,12 +36,12 @@ (def: .public empty Registry - (:abstraction [#artifacts sequence.empty - #resolver (dictionary.empty text.hash)])) + (abstraction [#artifacts sequence.empty + #resolver (dictionary.empty text.hash)])) (def: .public artifacts (-> Registry (Sequence [Artifact (Set unit.ID)])) - (|>> :representation (the #artifacts))) + (|>> representation (the #artifacts))) (def: next (-> Registry ID) @@ -52,12 +52,12 @@ (let [id (..next registry)] [id (|> registry - :representation + representation (revised #artifacts (sequence.suffix [[//.#id id //.#category {//category.#Anonymous} //.#mandatory? mandatory?] dependencies])) - :abstraction)])) + abstraction)])) (template [<tag> <create> <fetch> <type> <name> <+resolver>] [(def: .public (<create> it mandatory? dependencies registry) @@ -65,18 +65,18 @@ (let [id (..next registry)] [id (|> registry - :representation + representation (revised #artifacts (sequence.suffix [[//.#id id //.#category {<tag> it} //.#mandatory? mandatory?] dependencies])) - (revised #resolver (dictionary.has (<name> it) [id (: (Maybe //category.Definition) <+resolver>)])) - :abstraction)])) + (revised #resolver (dictionary.has (<name> it) [id (is (Maybe //category.Definition) <+resolver>)])) + abstraction)])) (def: .public (<fetch> registry) (-> Registry (List <type>)) (|> registry - :representation + representation (the #artifacts) sequence.list (list.all (|>> product.left @@ -96,7 +96,7 @@ (def: .public (find_definition name registry) (-> Text Registry (Maybe [ID (Maybe //category.Definition)])) - (|> (:representation registry) + (|> (representation registry) (the #resolver) (dictionary.value name))) @@ -106,37 +106,37 @@ (def: .public writer (Writer Registry) - (let [definition (: (Writer //category.Definition) - ($_ binary.and - binary.text - (binary.maybe - ($_ binary.and - binary.nat - binary.nat - binary.nat - )) - )) - category (: (Writer Category) - (function (_ value) - (case value - (^.template [<nat> <tag> <writer>] - [{<tag> value} - ((binary.and binary.nat <writer>) [<nat> value])]) - ([0 //category.#Anonymous binary.any] - [1 //category.#Definition definition] - [2 //category.#Analyser binary.text] - [3 //category.#Synthesizer binary.text] - [4 //category.#Generator binary.text] - [5 //category.#Directive binary.text] - [6 //category.#Custom binary.text])))) + (let [definition (is (Writer //category.Definition) + ($_ binary.and + binary.text + (binary.maybe + ($_ binary.and + binary.nat + binary.nat + binary.nat + )) + )) + category (is (Writer Category) + (function (_ value) + (case value + (^.template [<nat> <tag> <writer>] + [{<tag> value} + ((binary.and binary.nat <writer>) [<nat> value])]) + ([0 //category.#Anonymous binary.any] + [1 //category.#Definition definition] + [2 //category.#Analyser binary.text] + [3 //category.#Synthesizer binary.text] + [4 //category.#Generator binary.text] + [5 //category.#Directive binary.text] + [6 //category.#Custom binary.text])))) mandatory? binary.bit - dependency (: (Writer unit.ID) - (binary.and binary.nat binary.nat)) - dependencies (: (Writer (Set unit.ID)) - (binary.set dependency)) - artifacts (: (Writer (Sequence [Category Bit (Set unit.ID)])) - (binary.sequence/64 ($_ binary.and category mandatory? dependencies)))] - (|>> :representation + dependency (is (Writer unit.ID) + (binary.and binary.nat binary.nat)) + dependencies (is (Writer (Set unit.ID)) + (binary.set dependency)) + artifacts (is (Writer (Sequence [Category Bit (Set unit.ID)])) + (binary.sequence/64 ($_ binary.and category mandatory? dependencies)))] + (|>> representation (the #artifacts) (sequence#each (function (_ [it dependencies]) [(the //.#category it) @@ -150,37 +150,37 @@ (def: .public parser (Parser Registry) - (let [definition (: (Parser //category.Definition) - ($_ <>.and - <binary>.text - (<binary>.maybe - ($_ <>.and - <binary>.nat - <binary>.nat - <binary>.nat - )) - )) - category (: (Parser Category) - (do [! <>.monad] - [tag <binary>.nat] - (case tag - (^.template [<nat> <tag> <parser>] - [<nat> - (# ! each (|>> {<tag>}) <parser>)]) - ([0 //category.#Anonymous <binary>.any] - [1 //category.#Definition definition] - [2 //category.#Analyser <binary>.text] - [3 //category.#Synthesizer <binary>.text] - [4 //category.#Generator <binary>.text] - [5 //category.#Directive <binary>.text] - [6 //category.#Custom <binary>.text]) - - _ (<>.failure (exception.error ..invalid_category [tag]))))) + (let [definition (is (Parser //category.Definition) + ($_ <>.and + <binary>.text + (<binary>.maybe + ($_ <>.and + <binary>.nat + <binary>.nat + <binary>.nat + )) + )) + category (is (Parser Category) + (do [! <>.monad] + [tag <binary>.nat] + (case tag + (^.template [<nat> <tag> <parser>] + [<nat> + (# ! each (|>> {<tag>}) <parser>)]) + ([0 //category.#Anonymous <binary>.any] + [1 //category.#Definition definition] + [2 //category.#Analyser <binary>.text] + [3 //category.#Synthesizer <binary>.text] + [4 //category.#Generator <binary>.text] + [5 //category.#Directive <binary>.text] + [6 //category.#Custom <binary>.text]) + + _ (<>.failure (exception.error ..invalid_category [tag]))))) mandatory? <binary>.bit - dependency (: (Parser unit.ID) - (<>.and <binary>.nat <binary>.nat)) - dependencies (: (Parser (Set unit.ID)) - (<binary>.set unit.hash dependency))] + dependency (is (Parser unit.ID) + (<>.and <binary>.nat <binary>.nat)) + dependencies (is (Parser (Set unit.ID)) + (<binary>.set unit.hash dependency))] (|> (<binary>.sequence/64 ($_ <>.and category mandatory? dependencies)) (# <>.monad each (sequence#mix (function (_ [category mandatory? dependencies] registry) (product.right diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/module.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/module.lux index 4fd7fdebf..2db68a99d 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/module.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/dependency/module.lux @@ -54,17 +54,17 @@ (def: (ancestry archive) (-> Archive Graph) - (let [memo (: (Memo descriptor.Module Ancestry) - (function (_ again module) - (do [! state.monad] - [.let [parents (case (archive.find module archive) - {try.#Success [module output registry]} - (the [module.#descriptor descriptor.#references] module) - - {try.#Failure error} - ..fresh)] - ancestors (monad.each ! again (set.list parents))] - (in (list#mix set.union parents ancestors))))) + (let [memo (is (Memo descriptor.Module Ancestry) + (function (_ again module) + (do [! state.monad] + [.let [parents (case (archive.find module archive) + {try.#Success [module output registry]} + (the [module.#descriptor descriptor.#references] module) + + {try.#Failure error} + ..fresh)] + ancestors (monad.each ! again (set.list parents))] + (in (list#mix set.union parents ancestors))))) ancestry (memo.open memo)] (list#mix (function (_ module memory) (if (dictionary.key? memory module) diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/module.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/module.lux index 4d593aeda..869aa2019 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/module.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/module.lux @@ -98,5 +98,5 @@ (|> path (# fs read) (# ! each (|>> [name]))))))] - (in (dictionary.of_list text.hash (for @.old (:as (List [Text Binary]) pairs) + (in (dictionary.of_list text.hash (for @.old (as (List [Text Binary]) pairs) pairs))))) diff --git a/stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux b/stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux index e393253e1..55701b3f3 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cache/purge.lux @@ -68,8 +68,8 @@ (def: .public (purge caches load_order) (-> (List Cache) (dependency.Order Any) Purge) (list#mix (function (_ [module_name [@module entry]] purge) - (let [purged? (: (Predicate descriptor.Module) - (dictionary.key? purge))] + (let [purged? (is (Predicate descriptor.Module) + (dictionary.key? purge))] (if (purged? module_name) purge (if (|> entry diff --git a/stdlib/source/library/lux/tool/compiler/meta/cli.lux b/stdlib/source/library/lux/tool/compiler/meta/cli.lux index bbc2735e7..99f7da67a 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cli.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cli.lux @@ -86,15 +86,15 @@ (def: .public service (Parser Service) - (let [compilation (: (Parser Compilation) - ($_ <>.and - (<>.some ..host_dependency_parser) - (<>.some ..library_parser) - (<>.some ..compiler_parser) - (<>.some ..source_parser) - ..target_parser - ..module_parser - (<>.else configuration.empty ..configuration_parser)))] + (let [compilation (is (Parser Compilation) + ($_ <>.and + (<>.some ..host_dependency_parser) + (<>.some ..library_parser) + (<>.some ..compiler_parser) + (<>.some ..source_parser) + ..target_parser + ..module_parser + (<>.else configuration.empty ..configuration_parser)))] ($_ <>.or (<>.after (<cli>.this "build") compilation) diff --git a/stdlib/source/library/lux/tool/compiler/meta/cli/compiler.lux b/stdlib/source/library/lux/tool/compiler/meta/cli/compiler.lux index 9bc446b4d..09eef4deb 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/cli/compiler.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/cli/compiler.lux @@ -50,10 +50,10 @@ (def: .public parser (Parser Compiler) - (let [parameter (: (Parser Text) - (<| (<>.after (<text>.this ..start)) - (<>.before (<text>.this ..end)) - (<text>.slice (<text>.many! (<text>.none_of! ..end)))))] + (let [parameter (is (Parser Text) + (<| (<>.after (<text>.this ..start)) + (<>.before (<text>.this ..end)) + (<text>.slice (<text>.many! (<text>.none_of! ..end)))))] (do <>.monad [module parameter short parameter diff --git a/stdlib/source/library/lux/tool/compiler/meta/export.lux b/stdlib/source/library/lux/tool/compiler/meta/export.lux index 9b21de75b..7eb36ad62 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/export.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/export.lux @@ -38,9 +38,9 @@ (def: .public ownership tar.Ownership - (let [commons (: tar.Owner - [tar.#name tar.anonymous - tar.#id tar.no_id])] + (let [commons (is tar.Owner + [tar.#name tar.anonymous + tar.#id tar.no_id])] [tar.#user commons tar.#group commons])) diff --git a/stdlib/source/library/lux/tool/compiler/meta/import.lux b/stdlib/source/library/lux/tool/compiler/meta/import.lux index c485cb5f7..f0c390e3a 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/import.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/import.lux @@ -67,8 +67,8 @@ (def: .public (import system libraries) (-> (file.System Async) (List Library) (Action Import)) - (monad.mix (: (Monad Action) - (try.with async.monad)) + (monad.mix (is (Monad Action) + (try.with async.monad)) (..import_library system) (dictionary.empty text.hash) libraries)) diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux index 95d9a5e1a..05f766d5d 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux @@ -78,15 +78,15 @@ (def: (analysis_state host configuration archive) (-> Target Configuration Archive (Try .Lux)) (do [! try.monad] - [modules (: (Try (List [descriptor.Module .Module])) - (monad.each ! (function (_ module) - (do ! - [entry (archive.find module archive) - content (|> entry - (the [archive.#module module.#document]) - (document.content $.key))] - (in [module content]))) - (archive.archived archive)))] + [modules (is (Try (List [descriptor.Module .Module])) + (monad.each ! (function (_ module) + (do ! + [entry (archive.find module archive) + content (|> entry + (the [archive.#module module.#document]) + (document.content $.key))] + (in [module content]))) + (archive.archived archive)))] (in (has .#modules modules (fresh_analysis_state host configuration))))) (type: Definitions (Dictionary Text Any)) @@ -113,111 +113,111 @@ (-> Text (generation.Host expression directive) module.ID (Sequence [Artifact (Set unit.ID)]) (Dictionary Text Binary) (Document .Module) (Try [(Document .Module) Bundles Output]))) (do [! try.monad] - [[definitions bundles] (: (Try [Definitions Bundles Output]) - (loop [input (sequence.list expected) - definitions (: Definitions - (dictionary.empty text.hash)) - bundles ..empty_bundles - output (: Output sequence.empty)] - (let [[analysers synthesizers generators directives] bundles] - (case input - {.#Item [[[@artifact artifact_category mandatory_artifact?] artifact_dependencies] input']} - (case (do ! - [data (try.of_maybe (dictionary.value (format (%.nat @artifact) extension) actual)) - .let [context [@module @artifact] - directive (# host ingest context data)]] - (case artifact_category - {category.#Anonymous} - (do ! - [.let [output (sequence.suffix [@artifact {.#None} data] output)] - _ (# host re_learn context {.#None} directive)] - (in [definitions - [analysers - synthesizers - generators - directives] - output])) - - {category.#Definition [name function_artifact]} - (let [output (sequence.suffix [@artifact {.#None} data] output)] - (if (text#= $/program.name name) - (in [definitions - [analysers - synthesizers - generators - directives] - output]) - (do ! - [value (# host re_load context {.#None} directive)] - (in [(dictionary.has name value definitions) - [analysers - synthesizers - generators - directives] - output])))) + [[definitions bundles] (is (Try [Definitions Bundles Output]) + (loop [input (sequence.list expected) + definitions (is Definitions + (dictionary.empty text.hash)) + bundles ..empty_bundles + output (is Output sequence.empty)] + (let [[analysers synthesizers generators directives] bundles] + (case input + {.#Item [[[@artifact artifact_category mandatory_artifact?] artifact_dependencies] input']} + (case (do ! + [data (try.of_maybe (dictionary.value (format (%.nat @artifact) extension) actual)) + .let [context [@module @artifact] + directive (# host ingest context data)]] + (case artifact_category + {category.#Anonymous} + (do ! + [.let [output (sequence.suffix [@artifact {.#None} data] output)] + _ (# host re_learn context {.#None} directive)] + (in [definitions + [analysers + synthesizers + generators + directives] + output])) + + {category.#Definition [name function_artifact]} + (let [output (sequence.suffix [@artifact {.#None} data] output)] + (if (text#= $/program.name name) + (in [definitions + [analysers + synthesizers + generators + directives] + output]) + (do ! + [value (# host re_load context {.#None} directive)] + (in [(dictionary.has name value definitions) + [analysers + synthesizers + generators + directives] + output])))) - {category.#Analyser extension} - (do ! - [.let [output (sequence.suffix [@artifact {.#None} data] output)] - value (# host re_load context {.#None} directive)] - (in [definitions - [(dictionary.has extension (:as analysis.Handler value) analysers) - synthesizers - generators - directives] - output])) + {category.#Analyser extension} + (do ! + [.let [output (sequence.suffix [@artifact {.#None} data] output)] + value (# host re_load context {.#None} directive)] + (in [definitions + [(dictionary.has extension (as analysis.Handler value) analysers) + synthesizers + generators + directives] + output])) - {category.#Synthesizer extension} - (do ! - [.let [output (sequence.suffix [@artifact {.#None} data] output)] - value (# host re_load context {.#None} directive)] - (in [definitions - [analysers - (dictionary.has extension (:as synthesis.Handler value) synthesizers) - generators - directives] - output])) + {category.#Synthesizer extension} + (do ! + [.let [output (sequence.suffix [@artifact {.#None} data] output)] + value (# host re_load context {.#None} directive)] + (in [definitions + [analysers + (dictionary.has extension (as synthesis.Handler value) synthesizers) + generators + directives] + output])) - {category.#Generator extension} - (do ! - [.let [output (sequence.suffix [@artifact {.#None} data] output)] - value (# host re_load context {.#None} directive)] - (in [definitions - [analysers - synthesizers - (dictionary.has extension (:as generation.Handler value) generators) - directives] - output])) + {category.#Generator extension} + (do ! + [.let [output (sequence.suffix [@artifact {.#None} data] output)] + value (# host re_load context {.#None} directive)] + (in [definitions + [analysers + synthesizers + (dictionary.has extension (as generation.Handler value) generators) + directives] + output])) - {category.#Directive extension} - (do ! - [.let [output (sequence.suffix [@artifact {.#None} data] output)] - value (# host re_load context {.#None} directive)] - (in [definitions - [analysers - synthesizers - generators - (dictionary.has extension (:as directive.Handler value) directives)] - output])) + {category.#Directive extension} + (do ! + [.let [output (sequence.suffix [@artifact {.#None} data] output)] + value (# host re_load context {.#None} directive)] + (in [definitions + [analysers + synthesizers + generators + (dictionary.has extension (as directive.Handler value) directives)] + output])) - {category.#Custom name} - (do ! - [.let [output (sequence.suffix [@artifact {.#Some name} data] output)] - _ (# host re_learn context {.#Some name} directive)] - (in [definitions - [analysers - synthesizers - generators - directives] - output])))) - {try.#Success [definitions' bundles' output']} - (again input' definitions' bundles' output') + {category.#Custom name} + (do ! + [.let [output (sequence.suffix [@artifact {.#Some name} data] output)] + _ (# host re_learn context {.#Some name} directive)] + (in [definitions + [analysers + synthesizers + generators + directives] + output])))) + {try.#Success [definitions' bundles' output']} + (again input' definitions' bundles' output') - failure - failure) - - {.#End} - {try.#Success [definitions bundles output]})))) + failure + failure) + + {.#End} + {try.#Success [definitions bundles output]})))) content (document.content $.key document) definitions (monad.each ! (function (_ [def_name def_global]) (case def_global @@ -241,7 +241,7 @@ (dictionary.value def_name) try.of_maybe (# ! each (function (_ def_value) - [def_name {.#Type [exported? (:as .Type def_value) labels]}]))))) + [def_name {.#Type [exported? (as .Type def_value) labels]}]))))) (the .#definitions content))] (in [(document.document $.key (has .#definitions definitions content)) bundles]))) @@ -252,8 +252,8 @@ (archive.Entry .Module) (Async (Try [(archive.Entry .Module) Bundles])))) (do (try.with async.monad) - [actual (: (Async (Try (Dictionary Text Binary))) - (cache/module.artifacts async.monad fs context @module)) + [actual (is (Async (Try (Dictionary Text Binary))) + (cache/module.artifacts async.monad fs context @module)) .let [expected (registry.artifacts (the archive.#registry entry))] [document bundles output] (|> (the [archive.#module module.#document] entry) (loaded_document (the context.#artifact_extension context) host_environment @module expected actual) @@ -269,8 +269,8 @@ (def: (cache_parser customs) (-> (List Custom) (Parser [(module.Module Any) Registry])) - (case (for @.old (:as (List (Custom Any Any Any)) - customs) + (case (for @.old (as (List (Custom Any Any Any)) + customs) customs) {.#End} (..parser $.key $.parser) @@ -287,8 +287,8 @@ (Async (Try Cache))) (with_expansions [<cache> (as_is module_name @module module registry)] (do [! (try.with async.monad)] - [data (: (Async (Try Binary)) - (cache/module.cache fs context @module)) + [data (is (Async (Try Binary)) + (cache/module.cache fs context @module)) [module registry] (async#in (<binary>.result (..cache_parser customs) data))] (if (text#= descriptor.runtime module_name) (in [true <cache>]) @@ -314,7 +314,7 @@ (function (_ [_ [module @module |module| registry]] archive) (archive.has module [archive.#module |module| - archive.#output (: Output sequence.empty) + archive.#output (is Output sequence.empty) archive.#registry registry] archive)) archive) diff --git a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux index 00288e42b..3abcfbf5a 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux @@ -173,8 +173,8 @@ (def: .public (listing fs contexts) (-> (file.System Async) (List Context) (Action Enumeration)) - (let [! (: (Monad Action) - (try.with async.monad))] + (let [! (is (Monad Action) + (try.with async.monad))] (monad.mix ! (function (_ context enumeration) (do ! @@ -183,6 +183,6 @@ (format context (# fs separator)) context enumeration))) - (: Enumeration - (dictionary.empty text.hash)) + (is Enumeration + (dictionary.empty text.hash)) contexts))) diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux index df7f11ce0..ed360caec 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/ruby.lux @@ -1,7 +1,7 @@ (.using [library [lux "*" - [type {"+" :sharing}] + [type {"+" sharing}] [abstract ["[0]" monad {"+" do}]] [control @@ -62,12 +62,12 @@ (|> content (# utf8.codec decoded) (# ! each - (|>> :expected - (:sharing [directive] - directive - so_far - - directive) + (|>> as_expected + (sharing [directive] + directive + so_far + + directive) (_.then so_far))))) (_.comment "Lux module" (_.statement (_.string ""))) @@ -84,8 +84,8 @@ (List [module.ID [Text Binary]]) (Try (List [module.ID [Text Binary]]))) (do [! try.monad] - [bundle (: (Try (Maybe _.Statement)) - (..bundle_module module module_id necessary_dependencies (the archive.#output entry)))] + [bundle (is (Try (Maybe _.Statement)) + (..bundle_module module module_id necessary_dependencies (the archive.#output entry)))] (case bundle {.#None} (in sink) @@ -93,7 +93,7 @@ {.#Some bundle} (let [entry_content (|> (list) (list#mix _.then bundle) - (: _.Statement) + (is _.Statement) _.code (# utf8.codec encoded))] (in (list& [module_id [(..module_file module_id) entry_content]] @@ -127,11 +127,11 @@ (let [relative_path (_.do "gsub" (list (_.string main_file) (_.string (..module_file module_id))) {.#None} - (: _.CVar (_.manual "__FILE__")))] + (is _.CVar (_.manual "__FILE__")))] (_.statement (_.require/1 relative_path))))) (list#mix _.then (_.comment "Lux program" (_.statement (_.string "")))) - (: _.Statement) + (is _.Statement) _.code (# utf8.codec encoded))]] (in (|> entries diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux index f1dfb0189..c7548669a 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/scheme.lux @@ -1,7 +1,7 @@ (.using [library [lux {"-" Module} - [type {"+" :sharing}] + [type {"+" sharing}] [abstract ["[0]" monad {"+" do}]] [control @@ -63,14 +63,14 @@ (|> content (# encoding.utf8 decoded) (# try.monad each - (|>> :expected - (:sharing [directive] - directive - so_far - - directive) + (|>> as_expected + (sharing [directive] + directive + so_far + + directive) (..then so_far))))) - (: _.Expression (_.manual ""))))) + (is _.Expression (_.manual ""))))) (def: module_file (-> archive.ID file.Path) @@ -100,19 +100,19 @@ [Module [archive.ID [Descriptor (Document .Module) Output]]] (Try tar.Entry)) (do [! try.monad] - [bundle (: (Try _.Expression) - (..bundle_module output)) - entry_content (: (Try tar.Content) - (|> descriptor - (the descriptor.#references) - set.list - (list.all (function (_ module) (dictionary.value module mapping))) - (list#each (|>> ..module_file _.string _.load_relative/1)) - (list#mix ..then bundle) - (: _.Expression) - _.code - (# encoding.utf8 encoded) - tar.content)) + [bundle (is (Try _.Expression) + (..bundle_module output)) + entry_content (is (Try tar.Content) + (|> descriptor + (the descriptor.#references) + set.list + (list.all (function (_ module) (dictionary.value module mapping))) + (list#each (|>> ..module_file _.string _.load_relative/1)) + (list#mix ..then bundle) + (is _.Expression) + _.code + (# encoding.utf8 encoded) + tar.content)) module_file (tar.path (..module_file module_id))] (in {tar.#Normal [module_file now ..mode ..ownership entry_content]}))) @@ -125,7 +125,7 @@ (list#each (function (_ [module [module_id [descriptor document output]]]) [module module_id])) (dictionary.of_list text.hash) - (: (Dictionary Module archive.ID)))] + (is (Dictionary Module archive.ID)))] entries (monad.each ! (..write_module now mapping) order)] (in (|> entries sequence.of_list diff --git a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux index 1b867cd4f..37db58b89 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/packager/script.lux @@ -1,7 +1,7 @@ (.using [library [lux "*" - [type {"+" :sharing}] + [type {"+" sharing}] [abstract ["[0]" monad {"+" Monad do}]] [control @@ -49,12 +49,12 @@ (|> content (# utf8.codec decoded) (# try.monad each - (|>> :expected - (:sharing [directive] - directive - so_far - - directive) + (|>> as_expected + (sharing [directive] + directive + so_far + + directive) (sequence so_far))))) so_far))) diff --git a/stdlib/source/library/lux/tool/interpreter.lux b/stdlib/source/library/lux/tool/interpreter.lux index a5e907a52..7fc7687be 100644 --- a/stdlib/source/library/lux/tool/interpreter.lux +++ b/stdlib/source/library/lux/tool/interpreter.lux @@ -8,7 +8,7 @@ [data ["[0]" text ("[1]#[0]" equivalence) ["%" format {"+" format}]]] - [type {"+" :sharing} + [type {"+" sharing} ["[0]" check]] [compiler ["[0]" phase @@ -129,24 +129,24 @@ (-> Configuration Code <Interpretation>)) (function (_ state) (case (<| (phase.result' state) - (:sharing [anchor expression directive] - (State+ anchor expression directive) - state + (sharing [anchor expression directive] + (State+ anchor expression directive) + state - <Interpretation> - (interpret_directive code))) + <Interpretation> + (interpret_directive code))) {try.#Success [state' output]} {try.#Success [state' output]} {try.#Failure error} (if (ex.match? total.not_a_directive error) (<| (phase.result' state) - (:sharing [anchor expression directive] - (State+ anchor expression directive) - state - - <Interpretation> - (interpret_expression code))) + (sharing [anchor expression directive] + (State+ anchor expression directive) + state + + <Interpretation> + (interpret_expression code))) {try.#Failure error})))) ) @@ -177,20 +177,20 @@ [.let [[_where _offset _code] (the #source context)] [source' input] (syntax.parse ..module syntax.no_aliases (text.size _code) (the #source context)) [state' representation] (let [... TODO: Simplify ASAP - state (:sharing [anchor expression directive] - <Context> - context - - (State+ anchor expression directive) - (the #state context))] + state (sharing [anchor expression directive] + <Context> + context + + (State+ anchor expression directive) + (the #state context))] (<| (phase.result' state) ... TODO: Simplify ASAP - (:sharing [anchor expression directive] - <Context> - context - - (Operation anchor expression directive Text) - (execute (the #configuration context) input))))] + (sharing [anchor expression directive] + <Context> + context + + (Operation anchor expression directive Text) + (execute (the #configuration context) input))))] (in [(|> context (has #state state') (has #source source')) diff --git a/stdlib/source/library/lux/type.lux b/stdlib/source/library/lux/type.lux index 55fa0b166..8e7541755 100644 --- a/stdlib/source/library/lux/type.lux +++ b/stdlib/source/library/lux/type.lux @@ -1,6 +1,6 @@ (.using [library - [lux {"-" function :as} + [lux {"-" function as let} ["@" target] [abstract [equivalence {"+" Equivalence}] @@ -16,7 +16,7 @@ ["[0]" text ("[1]#[0]" monoid equivalence)] [collection ["[0]" array] - ["[0]" list ("[1]#[0]" functor monoid mix)]]] + ["[0]" list ("[1]#[0]" monad monoid mix)]]] ["[0]" macro [syntax {"+" syntax:}] ["^" pattern] @@ -48,7 +48,7 @@ (-> Type [(List Type) Type]) (case type {.#Function in out'} - (let [[ins out] (flat_function out')] + (.let [[ins out] (flat_function out')] [(list& in ins) out]) _ @@ -58,7 +58,7 @@ (-> Type [Type (List Type)]) (case type {.#Apply arg func'} - (let [[func args] (flat_application func')] + (.let [[func args] (flat_application func')] [func (list#composite args (list arg))]) _ @@ -103,7 +103,7 @@ [.#Product "[" "]" flat_tuple]) {.#Function input output} - (let [[ins out] (flat_function type)] + (.let [[ins out] (flat_function type)] ($_ text#composite "(-> " (|> ins (list#each format) @@ -122,7 +122,7 @@ ($_ text#composite "+" (n#encoded id)) {.#Apply param fun} - (let [[type_func type_args] (flat_application type)] + (.let [[type_func type_args] (flat_application type)] ($_ text#composite "(" (format type_func) " " (|> type_args (list#each format) list.reversed (list.interposed " ") (list#mix text#composite "")) ")")) (^.template [<tag> <desc>] @@ -370,7 +370,7 @@ (case type (^.multi (pattern {.#Primitive name (list element_type)}) (text#= array.type_name name)) - (let [[depth element_type] (flat_array element_type)] + (.let [[depth element_type] (flat_array element_type)] [(++ depth) element_type]) _ @@ -389,9 +389,9 @@ (def: secret_marker (`` (symbol (~~ (new_secret_marker))))) -(syntax: .public (:log! [input (<>.or (<>.and <code>.symbol - (<>.maybe (<>.after (<code>.symbol! ..secret_marker) <code>.any))) - <code>.any)]) +(syntax: .public (log! [input (<>.or (<>.and <code>.symbol + (<>.maybe (<>.after (<code>.symbol! ..secret_marker) <code>.any))) + <code>.any)]) (case input {.#Left [valueN valueC]} (do meta.monad @@ -399,7 +399,7 @@ valueT (meta.type valueN) .let [_ ("lux io log" ($_ text#composite - (symbol#encoded (symbol ..:log!)) " " (location.format location) text.new_line + (symbol#encoded (symbol ..log!)) " " (location.format location) text.new_line "Expression: " (case valueC {.#Some valueC} (code.format valueC) @@ -413,20 +413,20 @@ {.#Right valueC} (macro.with_symbols [g!value] (in (list (` (.let [(~ g!value) (~ valueC)] - (..:log! (~ valueC) (~ (code.symbol ..secret_marker)) (~ g!value))))))))) + (..log! (~ valueC) (~ (code.symbol ..secret_marker)) (~ g!value))))))))) (def: type_parameters (Parser (List Text)) (<code>.tuple (<>.some <code>.local_symbol))) -(syntax: .public (:as [type_vars type_parameters - input <code>.any - output <code>.any - value (<>.maybe <code>.any)]) +(syntax: .public (as [type_vars type_parameters + input <code>.any + output <code>.any + value (<>.maybe <code>.any)]) (macro.with_symbols [g!_] - (let [casterC (` (: (All ((~ g!_) (~+ (list#each code.local_symbol type_vars))) - (-> (~ input) (~ output))) - (|>> :expected)))] + (.let [casterC (` (is (All ((~ g!_) (~+ (list#each code.local_symbol type_vars))) + (-> (~ input) (~ output))) + (|>> as_expected)))] (case value {.#None} (in (list casterC)) @@ -444,30 +444,30 @@ (<>.and <code>.any <code>.any)) ... TODO: Make sure the generated code always gets optimized away. -(syntax: .public (:sharing [type_vars ..type_parameters - exemplar ..typed - computation ..typed]) +(syntax: .public (sharing [type_vars ..type_parameters + exemplar ..typed + computation ..typed]) (macro.with_symbols [g!_] - (let [typeC (` (All ((~ g!_) (~+ (list#each code.local_symbol type_vars))) - (-> (~ (the #type exemplar)) - (~ (the #type computation))))) - shareC (` (: (~ typeC) - (.function ((~ g!_) (~ g!_)) - (~ (the #expression computation)))))] + (.let [typeC (` (All ((~ g!_) (~+ (list#each code.local_symbol type_vars))) + (-> (~ (the #type exemplar)) + (~ (the #type computation))))) + shareC (` (is (~ typeC) + (.function ((~ g!_) (~ g!_)) + (~ (the #expression computation)))))] (in (list (` ((~ shareC) (~ (the #expression exemplar))))))))) -(syntax: .public (:by_example [type_vars ..type_parameters - exemplar ..typed - extraction <code>.any]) - (in (list (` (:of ((~! ..:sharing) - [(~+ (list#each code.local_symbol type_vars))] +(syntax: .public (by_example [type_vars ..type_parameters + exemplar ..typed + extraction <code>.any]) + (in (list (` (.type_of ((~! ..sharing) + [(~+ (list#each code.local_symbol type_vars))] - (~ (the #type exemplar)) - (~ (the #expression exemplar)) - - (~ extraction) - ... The value of this expression will never be relevant, so it doesn't matter what it is. - (.:as .Nothing []))))))) + (~ (the #type exemplar)) + (~ (the #expression exemplar)) + + (~ extraction) + ... The value of this expression will never be relevant, so it doesn't matter what it is. + (.as .Nothing []))))))) (def: .public (replaced before after) (-> Type Type Type Type) @@ -497,3 +497,11 @@ {.#Ex _} {.#Named _}) it)))) + +(syntax: .public (let [bindings (<code>.tuple (<>.some (<>.and <code>.any <code>.any))) + bodyT <code>.any]) + (in (list (` (..with_expansions [(~+ (|> bindings + (list#each (.function (_ [localT valueT]) + (list localT (` (..as_is (~ valueT)))))) + list#conjoint))] + (~ bodyT)))))) diff --git a/stdlib/source/library/lux/type/abstract.lux b/stdlib/source/library/lux/type/abstract.lux index 7f5f73fee..8ef8c93a1 100644 --- a/stdlib/source/library/lux/type/abstract.lux +++ b/stdlib/source/library/lux/type/abstract.lux @@ -1,6 +1,6 @@ (.using [library - [lux "*" + [lux {"-" pattern} ["[0]" meta] [abstract [monad {"+" Monad do}]] @@ -63,7 +63,7 @@ (!peek source reference (case head {.#Definition [exported? frame_type frame_value]} - (:as (Stack Frame) frame_value) + (as (Stack Frame) frame_value) (^.or {.#Type _} {.#Alias _} @@ -125,7 +125,7 @@ {.#Definition [exported? frames_type frames_value]} {.#Definition [exported? frames_type - (..push frame (:as (Stack Frame) frames_value))]} + (..push frame (as (Stack Frame) frames_value))]} (^.or {.#Type _} {.#Alias _} @@ -153,7 +153,7 @@ {.#Definition [exported? frames_type frames_value]} {.#Definition [exported? frames_type - (let [current_frames (:as (Stack Frame) frames_value)] + (let [current_frames (as (Stack Frame) frames_value)] (case (..pop current_frames) {.#Some current_frames'} current_frames' @@ -188,11 +188,11 @@ [(syntax: .public (<name> [[frame value] ..cast]) (do meta.monad [[name type_vars abstraction representation] (peek! frame)] - (in (list (` ((~! //.:as) [(~+ type_vars)] (~ <from>) (~ <to>) + (in (list (` ((~! //.as) [(~+ type_vars)] (~ <from>) (~ <to>) (~ value)))))))] - [:abstraction representation abstraction] - [:representation abstraction representation] + [abstraction representation abstraction] + [representation abstraction representation] ) (def: abstraction_type_name @@ -220,7 +220,7 @@ ))) ... TODO: Make sure the generated code always gets optimized away. -... (This applies to uses of ":abstraction" and ":representation") +... (This applies to uses of "abstraction" and "representation") (syntax: .public (abstract: [[export_policy [name type_vars] representation_type primitives] ..abstract]) (do meta.monad @@ -252,30 +252,30 @@ (<>.or (<>.and <code>.any parser) parser)) -(syntax: .public (:transmutation [selection (..selection <code>.any)]) +(syntax: .public (transmutation [selection (..selection <code>.any)]) (case selection {#Specific specific value} (in (list (` (.|> (~ value) - (..:representation (~ specific)) - (..:abstraction (~ specific)))))) + (..representation (~ specific)) + (..abstraction (~ specific)))))) {#Current value} - (in (list (` (.|> (~ value) ..:representation ..:abstraction)))))) + (in (list (` (.|> (~ value) ..representation ..abstraction)))))) -(syntax: .public (^:representation [selection (<code>.form (..selection <code>.local_symbol)) - body <code>.any - branches (<>.some <code>.any)]) +(syntax: .public (pattern [selection (<code>.form (..selection <code>.local_symbol)) + body <code>.any + branches (<>.some <code>.any)]) (case selection {#Specific specific name} (let [g!var (code.local_symbol name)] (in (list& g!var - (` (.let [(~ g!var) (..:representation (~ specific) (~ g!var))] + (` (.let [(~ g!var) (..representation (~ specific) (~ g!var))] (~ body))) branches))) {#Current name} (let [g!var (code.local_symbol name)] (in (list& g!var - (` (.let [(~ g!var) (..:representation (~ g!var))] + (` (.let [(~ g!var) (..representation (~ g!var))] (~ body))) branches))))) diff --git a/stdlib/source/library/lux/type/check.lux b/stdlib/source/library/lux/type/check.lux index a4312b3e8..541134b70 100644 --- a/stdlib/source/library/lux/type/check.lux +++ b/stdlib/source/library/lux/type/check.lux @@ -366,17 +366,17 @@ (-> Var (Check Any)) (function (_ context) {try.#Success [(revised .#var_bindings - (list#mix (: (:let [binding [Nat (Maybe Type)]] - (-> binding - (List binding) - (List binding))) - (function (_ in out) - (let [[@var :var:] in] - (if (n.= @ @var) - out - (list& in out))))) - (: (List [Nat (Maybe Type)]) - (list))) + (list#mix (is (//.let [binding [Nat (Maybe Type)]] + (-> binding + (List binding) + (List binding))) + (function (_ in out) + (let [[@var :var:] in] + (if (n.= @ @var) + out + (list& in out))))) + (is (List [Nat (Maybe Type)]) + (list))) context) []]})) diff --git a/stdlib/source/library/lux/type/dynamic.lux b/stdlib/source/library/lux/type/dynamic.lux index 28c9b7e35..d4f06d136 100644 --- a/stdlib/source/library/lux/type/dynamic.lux +++ b/stdlib/source/library/lux/type/dynamic.lux @@ -1,6 +1,6 @@ (.using [library - [lux "*" + [lux {"-" static} ["[0]" debug] [control ["[0]" try {"+" Try}] @@ -13,7 +13,7 @@ [macro {"+" with_symbols} ["[0]" syntax {"+" syntax:}]] ["[0]" type - abstract]]]) + ["[0]" abstract {"+" abstract:}]]]]) (exception: .public (wrong_type [expected Type actual Type]) @@ -26,29 +26,29 @@ (def: abstraction (-> [Type Any] Dynamic) - (|>> :abstraction)) + (|>> abstract.abstraction)) (def: representation (-> Dynamic [Type Any]) - (|>> :representation)) + (|>> abstract.representation)) - (syntax: .public (:dynamic [value <code>.any]) + (syntax: .public (dynamic [value <code>.any]) (with_symbols [g!value] - (in (list (` (let [(~ g!value) (~ value)] - ((~! ..abstraction) [(:of (~ g!value)) (~ g!value)]))))))) + (in (list (` (.let [(~ g!value) (~ value)] + ((~! ..abstraction) [(.type_of (~ g!value)) (~ g!value)]))))))) - (syntax: .public (:static [type <code>.any - value <code>.any]) + (syntax: .public (static [type <code>.any + value <code>.any]) (with_symbols [g!type g!value] - (in (list (` (let [[(~ g!type) (~ g!value)] ((~! ..representation) (~ value))] - (: ((~! try.Try) (~ type)) - (if (# (~! type.equivalence) (~' =) - (.type (~ type)) (~ g!type)) - {try.#Success (:as (~ type) (~ g!value))} - ((~! exception.except) ..wrong_type [(.type (~ type)) (~ g!type)]))))))))) + (in (list (` (.let [[(~ g!type) (~ g!value)] ((~! ..representation) (~ value))] + (.is ((~! try.Try) (~ type)) + (.if (.# (~! type.equivalence) (~' =) + (.type (~ type)) (~ g!type)) + {try.#Success (.as (~ type) (~ g!value))} + ((~! exception.except) ..wrong_type [(.type (~ type)) (~ g!type)]))))))))) (def: .public (format value) (-> Dynamic (Try Text)) - (let [[type value] (:representation value)] + (let [[type value] (abstract.representation value)] (debug.representation type value))) ) diff --git a/stdlib/source/library/lux/type/implicit.lux b/stdlib/source/library/lux/type/implicit.lux index 25678f37a..828656a46 100644 --- a/stdlib/source/library/lux/type/implicit.lux +++ b/stdlib/source/library/lux/type/implicit.lux @@ -150,8 +150,8 @@ [local_batches meta.locals .let [total_locals (list#mix (function (_ [name type] table) (try.else table (dictionary.has' name type table))) - (: (Dictionary Text Type) - (dictionary.empty text.hash)) + (is (Dictionary Text Type) + (dictionary.empty text.hash)) (list#conjoint local_batches))]] (in (|> total_locals dictionary.entries diff --git a/stdlib/source/library/lux/type/poly.lux b/stdlib/source/library/lux/type/poly.lux index 7f31f5187..de4a5ac58 100644 --- a/stdlib/source/library/lux/type/poly.lux +++ b/stdlib/source/library/lux/type/poly.lux @@ -38,11 +38,11 @@ (in (.list (` ((~! syntax:) (~ export_policy) ((~ g!name) [(~ g!type) (~! <code>.any)]) ((~! do) (~! meta.monad) [(~ g!type) ((~! meta.eval) .Type (~ g!type))] - (case (: (.Either .Text .Code) - ((~! <type>.result) ((~! <>.rec) - (function ((~ g!_) (~ g!name)) - (~ body))) - (.:as .Type (~ g!type)))) + (case (is (.Either .Text .Code) + ((~! <type>.result) ((~! <>.rec) + (function ((~ g!_) (~ g!name)) + (~ body))) + (.as .Type (~ g!type)))) {.#Left (~ g!output)} ((~! meta.failure) (~ g!output)) diff --git a/stdlib/source/library/lux/type/quotient.lux b/stdlib/source/library/lux/type/quotient.lux index 591734219..bd190b7b5 100644 --- a/stdlib/source/library/lux/type/quotient.lux +++ b/stdlib/source/library/lux/type/quotient.lux @@ -9,7 +9,7 @@ [macro {"+" with_symbols} [syntax {"+" syntax:}]] ["[0]" type - abstract]]]) + [abstract {"-" pattern}]]]]) (abstract: .public (Class t c %) (-> t c) @@ -18,7 +18,7 @@ (All (_ t c) (Ex (_ %) (-> (-> t c) (Class t c %)))) - (|>> :abstraction)) + (|>> abstraction)) (abstract: .public (Quotient t c %) (Record @@ -29,13 +29,13 @@ (All (_ t c %) (-> (Class t c %) t (Quotient t c %))) - (:abstraction [#value value - #label ((:representation Class class) value)])) + (abstraction [#value value + #label ((representation Class class) value)])) (template [<name> <output> <slot>] [(def: .public <name> (All (_ t c %) (-> (Quotient t c %) <output>)) - (|>> :representation (the <slot>)))] + (|>> representation (the <slot>)))] [value t #value] [label c #label] @@ -44,14 +44,26 @@ ) (syntax: .public (type [class <code>.any]) - (with_symbols [g!t g!c g!%] - (in (list (` ((~! type.:by_example) - [(~ g!t) (~ g!c) (~ g!%)] - - (..Class (~ g!t) (~ g!c) (~ g!%)) - (~ class) - - (..Quotient (~ g!t) (~ g!c) (~ g!%)))))))) + ... TODO: Switch to the cleaner approach ASAP. + (with_symbols [g!t g!c g!% g!_ g!:quotient:] + (in (list (` (let [... (~ g!_) (.is (.Ex ((~ g!_) (~ g!t) (~ g!c) (~ g!%)) + ... (..Class (~ g!t) (~ g!c) (~ g!%))) + ... (~ class)) + ] + (.case (.type_of (~ class)) + {.#Apply (~ g!%) {.#Apply (~ g!c) {.#Apply (~ g!t) (~ g!:quotient:)}}} + (.type (..Quotient (~ g!t) (~ g!c) (~ g!%))) + + (~ g!_) + (.undefined)))) + ... (` ((~! type.by_example) + ... [(~ g!t) (~ g!c) (~ g!%)] + + ... (..Class (~ g!t) (~ g!c) (~ g!%)) + ... (~ class) + + ... (..Quotient (~ g!t) (~ g!c) (~ g!%)))) + )))) (implementation: .public (equivalence super) (All (_ t c %) (-> (Equivalence c) (Equivalence (..Quotient t c %)))) diff --git a/stdlib/source/library/lux/type/refinement.lux b/stdlib/source/library/lux/type/refinement.lux index 304d7a07b..c4ac00c29 100644 --- a/stdlib/source/library/lux/type/refinement.lux +++ b/stdlib/source/library/lux/type/refinement.lux @@ -9,7 +9,7 @@ ["[0]" macro [syntax {"+" syntax:}]] ["[0]" type - abstract]]]) + [abstract {"-" pattern}]]]]) (abstract: .public (Refined t %) (Record @@ -25,14 +25,14 @@ (-> (Predicate t) (Refiner t %)))) (function (_ value) (if (predicate value) - {.#Some (:abstraction [#value value - #predicate predicate])} + {.#Some (abstraction [#value value + #predicate predicate])} {.#None}))) (template [<name> <output> <slot>] [(def: .public <name> (All (_ t %) (-> (Refined t %) <output>)) - (|>> :representation (the <slot>)))] + (|>> representation (the <slot>)))] [value t #value] [predicate (Predicate t) #predicate] @@ -43,11 +43,11 @@ (-> (-> t t) (-> (Refined t %) (Maybe (Refined t %))))) (function (_ refined) - (let [(open "_[0]") (:representation refined) + (let [(open "_[0]") (representation refined) value' (transform _#value)] (if (_#predicate value') - {.#Some (:abstraction [..#value value' - ..#predicate _#predicate])} + {.#Some (abstraction [..#value value' + ..#predicate _#predicate])} {.#None})))) ) @@ -85,9 +85,21 @@ {.#Item head no}])))) (syntax: .public (type [refiner <code>.any]) - (macro.with_symbols [g!t g!%] - (in (list (` ((~! type.:by_example) [(~ g!t) (~ g!%)] - (..Refiner (~ g!t) (~ g!%)) - (~ refiner) - - (..Refined (~ g!t) (~ g!%)))))))) + ... TODO: Switch to the cleaner approach ASAP. + (macro.with_symbols [g!t g!% g!_ g!:refiner:] + (in (list (` (let [... (~ g!_) (.is (.Ex ((~ g!_) (~ g!t) (~ g!%)) + ... (..Refined (~ g!t) (~ g!%))) + ... (~ refiner)) + ] + (.case (.type_of (~ refiner)) + {.#Apply (~ g!%) {.#Apply (~ g!t) (~ g!:refiner:)}} + (.type (..Refined (~ g!t) (~ g!%))) + + (~ g!_) + (.undefined)))) + ... (` ((~! type.by_example) [(~ g!t) (~ g!%)] + ... (..Refiner (~ g!t) (~ g!%)) + ... (~ refiner) + + ... (..Refined (~ g!t) (~ g!%)))) + )))) diff --git a/stdlib/source/library/lux/type/resource.lux b/stdlib/source/library/lux/type/resource.lux index 4ac5a17c0..5ed5a5f7e 100644 --- a/stdlib/source/library/lux/type/resource.lux +++ b/stdlib/source/library/lux/type/resource.lux @@ -23,7 +23,7 @@ [number ["n" nat]]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) (type: .public (Procedure monad input output value) (-> input (monad [output value]))) @@ -75,7 +75,7 @@ (template [<name> <mode>] [(def: <name> (Ex (_ k) (-> Any (Key <mode> k))) - (|>> :abstraction))] + (|>> abstraction))] [ordered_key Ordered] [commutative_key Commutative] @@ -88,7 +88,7 @@ [(def: .public (<name> monad value) (All (_ ! v) (Ex (_ k) (-> (Monad !) v (Affine ! (Key <mode> k) (Res k v))))) (function (_ keys) - (# monad in [[(<key> []) keys] (:abstraction value)])))] + (# monad in [[(<key> []) keys] (abstraction value)])))] [ordered Ordered ..ordered_key] [commutative Commutative ..commutative_key] @@ -98,7 +98,7 @@ (All (_ ! v k m) (-> (Monad !) (Res k v) (Relevant ! (Key m k) v))) (function (_ [key keys]) - (# monad in [keys (:representation resource)]))) + (# monad in [keys (representation resource)]))) ) (exception: .public (index_cannot_be_repeated [index Nat]) @@ -141,20 +141,20 @@ (do maybe.monad [input (list.item from g!inputs)] (in (sequence.suffix input to)))) - (: (Sequence Code) sequence.empty) + (is (Sequence Code) sequence.empty) swaps) maybe.trusted sequence.list) g!inputsT+ (list#each (|>> (~) (..Key ..Commutative) (`)) g!inputs) g!outputsT+ (list#each (|>> (~) (..Key ..Commutative) (`)) g!outputs)]] - (in (list (` (: (All ((~ g!_) (~ g!!) (~+ g!inputs) (~ g!context)) - (-> ((~! monad.Monad) (~ g!!)) - (Procedure (~ g!!) - [(~+ g!inputsT+) (~ g!context)] - [(~+ g!outputsT+) (~ g!context)] - .Any))) - (function ((~ g!_) (~ g!!) [(~+ g!inputs) (~ g!context)]) - (# (~ g!!) (~' in) [[(~+ g!outputs) (~ g!context)] []])))))))))) + (in (list (` (is (All ((~ g!_) (~ g!!) (~+ g!inputs) (~ g!context)) + (-> ((~! monad.Monad) (~ g!!)) + (Procedure (~ g!!) + [(~+ g!inputsT+) (~ g!context)] + [(~+ g!outputsT+) (~ g!context)] + .Any))) + (function ((~ g!_) (~ g!!) [(~+ g!inputs) (~ g!context)]) + (# (~ g!!) (~' in) [[(~+ g!outputs) (~ g!context)] []])))))))))) (def: amount (Parser Nat) @@ -171,14 +171,14 @@ [g!keys (|> (macro.symbol "keys") (list.repeated amount) (monad.all !))] - (in (list (` (: (All ((~ g!_) (~ g!!) (~+ g!keys) (~ g!context)) - (-> ((~! monad.Monad) (~ g!!)) - (Procedure (~ g!!) - [<from> (~ g!context)] - [<to> (~ g!context)] - .Any))) - (function ((~ g!_) (~ g!!) [<from> (~ g!context)]) - (# (~ g!!) (~' in) [[<to> (~ g!context)] []])))))))))] + (in (list (` (is (All ((~ g!_) (~ g!!) (~+ g!keys) (~ g!context)) + (-> ((~! monad.Monad) (~ g!!)) + (Procedure (~ g!!) + [<from> (~ g!context)] + [<to> (~ g!context)] + .Any))) + (function ((~ g!_) (~ g!!) [<from> (~ g!context)]) + (# (~ g!!) (~' in) [[<to> (~ g!context)] []])))))))))] [group (~+ g!keys) [(~+ g!keys)]] [un_group [(~+ g!keys)] (~+ g!keys)] diff --git a/stdlib/source/library/lux/type/unit.lux b/stdlib/source/library/lux/type/unit.lux index 6da16af7e..08fc7770f 100644 --- a/stdlib/source/library/lux/type/unit.lux +++ b/stdlib/source/library/lux/type/unit.lux @@ -24,24 +24,24 @@ ["i" int] ["[0]" ratio {"+" Ratio}]]] [type - abstract]]]) + [abstract {"-" pattern}]]]]) (abstract: .public (Qty unit) Int (def: in' (All (_ unit) (-> Int (Qty unit))) - (|>> :abstraction)) + (|>> abstraction)) (def: out' (All (_ unit) (-> (Qty unit) Int)) - (|>> :representation)) + (|>> representation)) (template [<name> <op>] [(def: .public (<name> param subject) (All (_ unit) (-> (Qty unit) (Qty unit) (Qty unit))) - (:abstraction (<op> (:representation param) - (:representation subject))))] + (abstraction (<op> (representation param) + (representation subject))))] [+ i.+] [- i.-] @@ -50,8 +50,8 @@ (template [<name> <op> <p> <s> <p*s>] [(def: .public (<name> param subject) (All (_ p s) (-> (Qty <p>) (Qty <s>) (Qty <p*s>))) - (:abstraction (<op> (:representation param) - (:representation subject))))] + (abstraction (<op> (representation param) + (representation subject))))] [* i.* p s [p s]] [/ i./ p [p s] s] @@ -60,19 +60,19 @@ (type: .public (Unit a) (Interface - (: (-> Int (Qty a)) - in) - (: (-> (Qty a) Int) - out))) + (is (-> Int (Qty a)) + in) + (is (-> (Qty a) Int) + out))) (type: .public (Scale s) (Interface - (: (All (_ u) (-> (Qty u) (Qty (s u)))) - scale) - (: (All (_ u) (-> (Qty (s u)) (Qty u))) - de_scale) - (: Ratio - ratio))) + (is (All (_ u) (-> (Qty u) (Qty (s u)))) + scale) + (is (All (_ u) (-> (Qty (s u)) (Qty u))) + de_scale) + (is Ratio + ratio))) (type: .public Pure (Qty Any)) diff --git a/stdlib/source/library/lux/world/console.lux b/stdlib/source/library/lux/world/console.lux index 5f0fef818..74700b18b 100644 --- a/stdlib/source/library/lux/world/console.lux +++ b/stdlib/source/library/lux/world/console.lux @@ -19,14 +19,14 @@ (type: .public (Console !) (Interface - (: (-> [] (! (Try Char))) - read) - (: (-> [] (! (Try Text))) - read_line) - (: (-> Text (! (Try Any))) - write) - (: (-> [] (! (Try Any))) - close))) + (is (-> [] (! (Try Char))) + read) + (is (-> [] (! (Try Text))) + read_line) + (is (-> Text (! (Try Any))) + write) + (is (-> [] (! (Try Any))) + close))) (def: .public (async console) (-> (Console IO) (Console Async)) @@ -78,7 +78,7 @@ jvm_output (java/lang/System::out)] (<| in {try.#Success} - (: (Console IO)) ... TODO: Remove ASAP + (is (Console IO)) ... TODO: Remove ASAP (implementation (def: (read _) (|> jvm_input @@ -123,8 +123,8 @@ (case (Readable_Stream::read it) {.#Some buffer} (let [input (Buffer::toString buffer)] - (case (: (Maybe [<type> Text]) - <query>) + (case (is (Maybe [<type> Text]) + <query>) {.#Some [head tail]} (exec (Readable_Stream::unshift|String tail it) @@ -152,8 +152,8 @@ (!read Text (text.split_by text.\n input))) (def: (write it) - (let [[read! write!] (: [(async.Async (Try [])) (async.Resolver (Try []))] - (async.async []))] + (let [[read! write!] (is [(async.Async (Try [])) (async.Resolver (Try []))] + (async.async []))] (exec (Writable_Stream::write it (ffi.function (_ []) Any (io.run! (write! {try.#Success []}))) (process::stdout)) @@ -170,14 +170,14 @@ (type: .public (Mock s) (Interface - (: (-> s (Try [s Char])) - on_read) - (: (-> s (Try [s Text])) - on_read_line) - (: (-> Text s (Try s)) - on_write) - (: (-> s (Try s)) - on_close))) + (is (-> s (Try [s Char])) + on_read) + (is (-> s (Try [s Text])) + on_read_line) + (is (-> Text s (Try s)) + on_write) + (is (-> s (Try s)) + on_close))) (def: .public (mock mock init) (All (_ s) (-> (Mock s) s (Console IO))) diff --git a/stdlib/source/library/lux/world/db/jdbc.lux b/stdlib/source/library/lux/world/db/jdbc.lux index 25a29b3b3..748f2955d 100644 --- a/stdlib/source/library/lux/world/db/jdbc.lux +++ b/stdlib/source/library/lux/world/db/jdbc.lux @@ -81,14 +81,14 @@ (type: .public (DB !) (Interface - (: (Can_Execute !) - execute) - (: (Can_Insert !) - insert) - (: (Can_Query !) - query) - (: (Can_Close !) - close))) + (is (Can_Execute !) + execute) + (is (Can_Insert !) + insert) + (is (Can_Query !) + query) + (is (Can_Close !) + close))) (def: (with_statement statement conn action) (All (_ i a) @@ -121,41 +121,41 @@ [connection (java/sql/DriverManager::getConnection (the #url creds) (the #user creds) (the #password creds))] - (in (: (DB IO) - (implementation - (def: execute - (..can_execute - (function (execute statement) - (with_statement statement connection - (function (_ prepared) - (do (try.with io.monad) - [row_count (java/sql/PreparedStatement::executeUpdate prepared)] - (in (.nat row_count)))))))) - - (def: insert - (..can_insert - (function (insert statement) - (with_statement statement connection - (function (_ prepared) - (do (try.with io.monad) - [_ (java/sql/PreparedStatement::executeUpdate prepared) - result_set (io.io (java/sql/Statement::getGeneratedKeys prepared))] - (/output.rows /output.long result_set))))))) - - (def: close - (..can_close - (function (close _) - (java/sql/Connection::close connection)))) - - (def: query - (..can_query - (function (query [statement output]) - (with_statement statement connection - (function (_ prepared) - (do (try.with io.monad) - [result_set (java/sql/PreparedStatement::executeQuery prepared)] - (/output.rows output result_set))))))) - ))))) + (in (is (DB IO) + (implementation + (def: execute + (..can_execute + (function (execute statement) + (with_statement statement connection + (function (_ prepared) + (do (try.with io.monad) + [row_count (java/sql/PreparedStatement::executeUpdate prepared)] + (in (.nat row_count)))))))) + + (def: insert + (..can_insert + (function (insert statement) + (with_statement statement connection + (function (_ prepared) + (do (try.with io.monad) + [_ (java/sql/PreparedStatement::executeUpdate prepared) + result_set (io.io (java/sql/Statement::getGeneratedKeys prepared))] + (/output.rows /output.long result_set))))))) + + (def: close + (..can_close + (function (close _) + (java/sql/Connection::close connection)))) + + (def: query + (..can_query + (function (query [statement output]) + (with_statement statement connection + (function (_ prepared) + (do (try.with io.monad) + [result_set (java/sql/PreparedStatement::executeQuery prepared)] + (/output.rows output result_set))))))) + ))))) (def: .public (with_db creds action) (All (_ a) diff --git a/stdlib/source/library/lux/world/db/sql.lux b/stdlib/source/library/lux/world/db/sql.lux index d3cb4856f..f43d12af6 100644 --- a/stdlib/source/library/lux/world/db/sql.lux +++ b/stdlib/source/library/lux/world/db/sql.lux @@ -1,19 +1,19 @@ (.using - [library - [lux {"-" Source Definition function and or not type int} - [control - [monad {"+" do}]] - [data - [number - ["i" int]] - ["[0]" text ("[1]#[0]" equivalence) - ["%" format {"+" format}]] - [collection - ["[0]" list ("[1]#[0]" functor)]]] - [macro - ["[0]" template]] - [type - abstract]]]) + [library + [lux {"-" Source Definition function and or not type int} + [control + [monad {"+" do}]] + [data + [number + ["i" int]] + ["[0]" text ("[1]#[0]" equivalence) + ["%" format {"+" format}]] + [collection + ["[0]" list ("[1]#[0]" functor)]]] + [macro + ["[0]" template]] + [type + [abstract {"-" pattern}]]]]) (def: parenthesize (-> Text Text) @@ -104,23 +104,23 @@ ... Do not use this function to actually execute SQL code. (def: .public read (-> (SQL Any) Text) - (|>> :representation)) + (|>> representation)) (def: .public (sql action) (-> Statement Text) - (format (:representation action) ";")) + (format (representation action) ";")) (def: listing (-> (List (SQL Any)) Text) - (|>> (list#each (|>> :representation)) + (|>> (list#each (|>> representation)) (text.interposed ", "))) ... Value - (def: .public ? Placeholder (:abstraction "?")) + (def: .public ? Placeholder (abstraction "?")) (def: literal (-> Text Literal) - (|>> :abstraction)) + (|>> abstraction)) (def: .public null Literal (..literal "NULL")) @@ -132,22 +132,22 @@ (def: .public function (-> Text Function) - (|>> :abstraction)) + (|>> abstraction)) (def: .public (call function parameters) (-> Function (List Value) Value) - (:abstraction (format (:representation function) - (..parenthesize (..listing parameters))))) + (abstraction (format (representation function) + (..parenthesize (..listing parameters))))) ... Condition (template [<name> <sql_op>] [(def: .public (<name> reference sample) (-> Value Value Condition) - (:abstraction + (abstraction (..parenthesize - (format (:representation sample) + (format (representation sample) " " <sql_op> " " - (:representation reference)))))] + (representation reference)))))] [= "="] [<> "<>"] @@ -162,26 +162,26 @@ (def: .public (between from to sample) (-> Value Value Value Condition) - (:abstraction + (abstraction (..parenthesize - (format (:representation sample) - " BETWEEN " (:representation from) - " AND " (:representation to))))) + (format (representation sample) + " BETWEEN " (representation from) + " AND " (representation to))))) (def: .public (in options value) (-> (List Value) Value Condition) - (:abstraction - (format (:representation value) + (abstraction + (format (representation value) " IN " (..parenthesize (listing options))))) (template [<func_name> <sql_op>] [(def: .public (<func_name> left right) (-> Condition Condition Condition) - (:abstraction - (format (..parenthesize (:representation left)) + (abstraction + (format (..parenthesize (representation left)) " " <sql_op> " " - (..parenthesize (:representation right)))))] + (..parenthesize (representation right)))))] [and "AND"] [or "OR"] @@ -190,7 +190,7 @@ (template [<name> <type> <sql>] [(def: .public <name> (-> <type> Condition) - (|>> :representation ..parenthesize (format <sql> " ") :abstraction))] + (|>> representation ..parenthesize (format <sql> " ") abstraction))] [not Condition "NOT"] [exists Any_Query "EXISTS"] @@ -200,7 +200,7 @@ (template [<name> <type> <decoration>] [(def: .public <name> (-> <type> Source) - (|>> :representation <decoration> :abstraction))] + (|>> representation <decoration> abstraction))] [from_table Table (<|)] [from_view View (<|)] @@ -210,7 +210,7 @@ (template [<func_name> <op>] [(def: .public (<func_name> columns source) (-> (List [Column Alias]) Source Base_Query) - (:abstraction + (abstraction (format <op> " " (case columns @@ -221,10 +221,10 @@ (|> columns (list#each (.function (_ [column alias]) (if (text#= ..no_alias alias) - (:representation column) - (format (:representation column) " AS " alias)))) + (representation column) + (format (representation column) " AS " alias)))) (text.interposed ", "))) - " FROM " (:representation source))))] + " FROM " (representation source))))] [select "SELECT"] @@ -234,11 +234,11 @@ (template [<name> <join_text>] [(def: .public (<name> table condition prev) (-> Table Condition Base_Query Base_Query) - (:abstraction - (format (:representation prev) + (abstraction + (format (representation prev) " " <join_text> " " - (:representation table) - " ON " (:representation condition))))] + (representation table) + " ON " (representation condition))))] [inner_join "INNER JOIN"] [left_join "LEFT JOIN"] @@ -249,10 +249,10 @@ (template [<function> <sql_op>] [(def: .public (<function> left right) (-> Any_Query Any_Query (Query Without_Where Without_Having No_Order No_Group No_Limit No_Offset)) - (:abstraction - (format (:representation left) + (abstraction + (format (representation left) " " <sql_op> " " - (:representation right))))] + (representation right))))] [union "UNION"] [union_all "UNION ALL"] @@ -263,8 +263,8 @@ [(`` (def: .public (<name> value query) (All (_ (~~ (template.spliced <variables>))) (-> Nat <input> <output>)) - (:abstraction - (format (:representation query) + (abstraction + (format (representation query) " " <sql> " " (%.nat value)))))] @@ -280,7 +280,7 @@ (template [<name> <sql>] [(def: .public <name> Order - (:abstraction <sql>))] + (abstraction <sql>))] [ascending "ASC"] [descending "DESC"] @@ -293,15 +293,15 @@ (Query where having With_Order group limit offset))) (case pairs {.#End} - (|> query :representation :abstraction) + (|> query representation abstraction) _ - (:abstraction - (format (:representation query) + (abstraction + (format (representation query) " ORDER BY " (|> pairs (list#each (.function (_ [value order]) - (format (:representation value) " " (:representation order)))) + (format (representation value) " " (representation order)))) (text.interposed ", ")))))) (def: .public (group_by pairs query) @@ -311,19 +311,19 @@ (Query where having order With_Group limit offset))) (case pairs {.#End} - (|> query :representation :abstraction) + (|> query representation abstraction) _ - (:abstraction - (format (:representation query) + (abstraction + (format (representation query) " GROUP BY " (..listing pairs))))) ... Command (def: .public (insert table columns rows) (-> Table (List Column) (List (List Value)) (Command Without_Where Without_Having)) - (:abstraction - (format "INSERT INTO " (:representation table) " " + (abstraction + (format "INSERT INTO " (representation table) " " (..parenthesize (..listing columns)) " VALUES " (|> rows @@ -333,48 +333,48 @@ (def: .public (update table pairs) (-> Table (List [Column Value]) (Command No_Where No_Having)) - (:abstraction (format "UPDATE " (:representation table) - (case pairs - {.#End} - "" - - _ - (format " SET " (|> pairs - (list#each (.function (_ [column value]) - (format (:representation column) "=" (:representation value)))) - (text.interposed ", "))))))) + (abstraction (format "UPDATE " (representation table) + (case pairs + {.#End} + "" + + _ + (format " SET " (|> pairs + (list#each (.function (_ [column value]) + (format (representation column) "=" (representation value)))) + (text.interposed ", "))))))) (def: .public delete (-> Table (Command No_Where No_Having)) - (|>> :representation (format "DELETE FROM ") :abstraction)) + (|>> representation (format "DELETE FROM ") abstraction)) ... Action (def: .public (where condition prev) (All (_ kind having) (-> Condition (Action No_Where having kind) (Action With_Where having kind))) - (:abstraction - (format (:representation prev) + (abstraction + (format (representation prev) " WHERE " - (:representation condition)))) + (representation condition)))) (def: .public (having condition prev) (All (_ where kind) (-> Condition (Action where No_Having kind) (Action where With_Having kind))) - (:abstraction - (format (:representation prev) + (abstraction + (format (representation prev) " HAVING " - (:representation condition)))) + (representation condition)))) ... Schema (def: .public type (-> Text (Schema Value)) - (|>> :abstraction)) + (|>> abstraction)) (template [<name> <attr>] [(def: .public (<name> attr) (-> (Schema Value) (Schema Value)) - (:abstraction - (format (:representation attr) " " <attr>)))] + (abstraction + (format (representation attr) " " <attr>)))] [unique "UNIQUE"] [not_null "NOT NULL"] @@ -383,38 +383,38 @@ (def: .public (default value attr) (-> Value (Schema Value) (Schema Value)) - (:abstraction - (format (:representation attr) " DEFAULT " (:representation value)))) + (abstraction + (format (representation attr) " DEFAULT " (representation value)))) (def: .public (define_column name type) (-> Column (Schema Value) (Schema Column)) - (:abstraction - (format (:representation name) " " (:representation type)))) + (abstraction + (format (representation name) " " (representation type)))) (def: .public (auto_increment offset column) (-> Int (Schema Column) (Schema Column)) - (:abstraction - (format (:representation column) " AUTO_INCREMENT=" (:representation (..int offset))))) + (abstraction + (format (representation column) " AUTO_INCREMENT=" (representation (..int offset))))) (def: .public (create_table or_replace? table columns) (-> Bit Table (List (Schema Column)) Definition) (let [command (if or_replace? "CREATE OR REPLACE TABLE" "CREATE TABLE IF NOT EXISTS")] - (:abstraction - (format command " " (:representation table) + (abstraction + (format command " " (representation table) (..parenthesize (..listing columns)))))) (def: .public (create_table_as table query) (-> Table Any_Query Definition) - (:abstraction - (format "CREATE TABLE " (:representation table) " AS " (:representation query)))) + (abstraction + (format "CREATE TABLE " (representation table) " AS " (representation query)))) (template [<name> <sql>] [(def: .public (<name> table) (-> Table Definition) - (:abstraction - (format <sql> " TABLE " (:representation table))))] + (abstraction + (format <sql> " TABLE " (representation table))))] [drop "DROP"] [truncate "TRUNCATE"] @@ -422,18 +422,18 @@ (def: .public (add_column table column) (-> Table (Schema Column) Definition) - (:abstraction - (format "ALTER TABLE " (:representation table) " ADD " (:representation column)))) + (abstraction + (format "ALTER TABLE " (representation table) " ADD " (representation column)))) (def: .public (drop_column table column) (-> Table Column Definition) - (:abstraction - (format "ALTER TABLE " (:representation table) " DROP COLUMN " (:representation column)))) + (abstraction + (format "ALTER TABLE " (representation table) " DROP COLUMN " (representation column)))) (template [<name> <type>] [(def: .public (<name> name) (-> Text <type>) - (:abstraction name))] + (abstraction name))] [column Column] [table Table] @@ -445,7 +445,7 @@ (template [<name> <type> <sql>] [(def: .public <name> (-> <type> Definition) - (|>> :representation (format <sql> " ") :abstraction))] + (|>> representation (format <sql> " ") abstraction))] [create_db DB "CREATE DATABASE"] [drop_db DB "DROP DATABASE"] @@ -455,8 +455,8 @@ (template [<name> <sql>] [(def: .public (<name> view query) (-> View Any_Query Definition) - (:abstraction - (format <sql> " " (:representation view) " AS " (:representation query))))] + (abstraction + (format <sql> " " (representation view) " AS " (representation query))))] [create_view "CREATE VIEW"] [create_or_replace_view "CREATE OR REPLACE VIEW"] @@ -464,17 +464,17 @@ (def: .public (create_index index table unique? columns) (-> Index Table Bit (List Column) Definition) - (:abstraction - (format "CREATE " (if unique? "UNIQUE" "") " INDEX " (:representation index) - " ON " (:representation table) " " (..parenthesize (..listing columns))))) + (abstraction + (format "CREATE " (if unique? "UNIQUE" "") " INDEX " (representation index) + " ON " (representation table) " " (..parenthesize (..listing columns))))) (def: .public (with alias query body) (All (_ where having order group limit offset) (-> Table Any_Query (Query where having order group limit offset) (Query where having order group limit offset))) - (:abstraction - (format "WITH " (:representation alias) - " AS " (..parenthesize (:representation query)) - " " (:representation body)))) + (abstraction + (format "WITH " (representation alias) + " AS " (..parenthesize (representation query)) + " " (representation body)))) ) diff --git a/stdlib/source/library/lux/world/file.lux b/stdlib/source/library/lux/world/file.lux index b50da2586..4e47a182b 100644 --- a/stdlib/source/library/lux/world/file.lux +++ b/stdlib/source/library/lux/world/file.lux @@ -43,20 +43,20 @@ (`` (type: .public (System !) (Interface - (: Text - separator) + (is Text + separator) (~~ (template [<name> <output>] - [(: (-> Path (! <output>)) - <name>)] + [(is (-> Path (! <output>)) + <name>)] [file? Bit] [directory? Bit] )) (~~ (template [<name> <output>] - [(: (-> Path (! (Try <output>))) - <name>)] + [(is (-> Path (! (Try <output>))) + <name>)] [make_directory Any] [directory_files (List Path)] @@ -70,8 +70,8 @@ )) (~~ (template [<name> <input>] - [(: (-> <input> Path (! (Try Any))) - <name>)] + [(is (-> <input> Path (! (Try Any))) + <name>)] [modify Instant] [write Binary] @@ -330,8 +330,8 @@ (template: (with_async <write> <type> <body>) [(template.with_locals [<read>] - (let [[<read> <write>] (: [(Async <type>) (async.Resolver <type>)] - (async.async []))] + (let [[<read> <write>] (is [(Async <type>) (async.Resolver <type>)] + (async.async []))] (exec <body> <read>)))]) @@ -366,7 +366,7 @@ io.run! write! (if (ffi.null? error) - {try.#Success (:expected datum)} + {try.#Success (as_expected datum)} {try.#Failure (Error::toString error)}))) (ffi.import: JsPath @@ -378,135 +378,135 @@ (do maybe.monad [node_fs (node_js.require "fs") node_path (node_js.require "path") - .let [node_fs (:as ..Fs node_fs) + .let [node_fs (as ..Fs node_fs) js_separator (if ffi.on_node_js? - (JsPath::sep (:as ..JsPath node_path)) + (JsPath::sep (as ..JsPath node_path)) "/")]] - (in (: (System Async) - (`` (implementation - (def: separator - js_separator) - - (~~ (template [<name> <method>] - [(def: (<name> path) - (do async.monad - [?stats (with_async write! (Try Stats) - (Fs::stat path (..value_callback write!) - node_fs))] - (in (case ?stats - {try.#Success stats} - (<method> stats) - - {try.#Failure _} - false))))] - - [file? Stats::isFile] - [directory? Stats::isDirectory] - )) - - (def: (make_directory path) - (do async.monad - [outcome (with_async write! (Try Any) - (Fs::access path - (|> node_fs Fs::constants FsConstants::F_OK) - (..any_callback write!) - node_fs))] - (case outcome - {try.#Success _} - (in (exception.except ..cannot_make_directory [path])) - - {try.#Failure _} + (in (is (System Async) + (`` (implementation + (def: separator + js_separator) + + (~~ (template [<name> <method>] + [(def: (<name> path) + (do async.monad + [?stats (with_async write! (Try Stats) + (Fs::stat path (..value_callback write!) + node_fs))] + (in (case ?stats + {try.#Success stats} + (<method> stats) + + {try.#Failure _} + false))))] + + [file? Stats::isFile] + [directory? Stats::isDirectory] + )) + + (def: (make_directory path) + (do async.monad + [outcome (with_async write! (Try Any) + (Fs::access path + (|> node_fs Fs::constants FsConstants::F_OK) + (..any_callback write!) + node_fs))] + (case outcome + {try.#Success _} + (in (exception.except ..cannot_make_directory [path])) + + {try.#Failure _} + (with_async write! (Try Any) + (Fs::mkdir path (..any_callback write!) node_fs))))) + + (~~ (template [<name> <method>] + [(def: (<name> path) + (do [! (try.with async.monad)] + [subs (with_async write! (Try (Array ffi.String)) + (Fs::readdir path (..value_callback write!) node_fs))] + (|> subs + (array.list {.#None}) + (list#each (|>> (format path js_separator))) + (monad.each ! (function (_ sub) + (# ! each (|>> <method> [sub]) + (with_async write! (Try Stats) + (Fs::stat sub (..value_callback write!) node_fs))))) + (# ! each (|>> (list.only product.right) + (list#each product.left))))))] + + [directory_files Stats::isFile] + [sub_directories Stats::isDirectory] + )) + + (def: (file_size path) + (do (try.with async.monad) + [stats (with_async write! (Try Stats) + (Fs::stat path (..value_callback write!) + node_fs))] + (in (|> stats + Stats::size + f.nat)))) + + (def: (last_modified path) + (do (try.with async.monad) + [stats (with_async write! (Try Stats) + (Fs::stat path (..value_callback write!) + node_fs))] + (in (|> stats + Stats::mtimeMs + f.int + duration.of_millis + instant.absolute)))) + + (def: (can_execute? path) + (# async.monad each + (|>> (pipe.case + {try.#Success _} + true + + {try.#Failure _} + false) + {try.#Success}) (with_async write! (Try Any) - (Fs::mkdir path (..any_callback write!) node_fs))))) - - (~~ (template [<name> <method>] - [(def: (<name> path) - (do [! (try.with async.monad)] - [subs (with_async write! (Try (Array ffi.String)) - (Fs::readdir path (..value_callback write!) node_fs))] - (|> subs - (array.list {.#None}) - (list#each (|>> (format path js_separator))) - (monad.each ! (function (_ sub) - (# ! each (|>> <method> [sub]) - (with_async write! (Try Stats) - (Fs::stat sub (..value_callback write!) node_fs))))) - (# ! each (|>> (list.only product.right) - (list#each product.left))))))] - - [directory_files Stats::isFile] - [sub_directories Stats::isDirectory] - )) - - (def: (file_size path) - (do (try.with async.monad) - [stats (with_async write! (Try Stats) - (Fs::stat path (..value_callback write!) - node_fs))] - (in (|> stats - Stats::size - f.nat)))) - - (def: (last_modified path) - (do (try.with async.monad) - [stats (with_async write! (Try Stats) - (Fs::stat path (..value_callback write!) - node_fs))] - (in (|> stats - Stats::mtimeMs - f.int - duration.of_millis - instant.absolute)))) - - (def: (can_execute? path) - (# async.monad each - (|>> (pipe.case - {try.#Success _} - true - - {try.#Failure _} - false) - {try.#Success}) + (Fs::access path + (|> node_fs Fs::constants FsConstants::X_OK) + (..any_callback write!) + node_fs)))) + + (def: (read path) + (with_async write! (Try Binary) + (Fs::readFile path (..value_callback write!) + node_fs))) + + (def: (delete path) + (do (try.with async.monad) + [stats (with_async write! (Try Stats) + (Fs::stat path (..value_callback write!) node_fs))] (with_async write! (Try Any) - (Fs::access path - (|> node_fs Fs::constants FsConstants::X_OK) - (..any_callback write!) + (if (Stats::isFile stats) + (Fs::unlink path (..any_callback write!) node_fs) + (Fs::rmdir path (..any_callback write!) node_fs))))) + + (def: (modify time_stamp path) + (with_async write! (Try Any) + (let [when (|> time_stamp instant.relative duration.millis i.frac)] + (Fs::utimes path when when (..any_callback write!) node_fs)))) - (def: (read path) - (with_async write! (Try Binary) - (Fs::readFile path (..value_callback write!) - node_fs))) - - (def: (delete path) - (do (try.with async.monad) - [stats (with_async write! (Try Stats) - (Fs::stat path (..value_callback write!) node_fs))] - (with_async write! (Try Any) - (if (Stats::isFile stats) - (Fs::unlink path (..any_callback write!) node_fs) - (Fs::rmdir path (..any_callback write!) node_fs))))) - - (def: (modify time_stamp path) - (with_async write! (Try Any) - (let [when (|> time_stamp instant.relative duration.millis i.frac)] - (Fs::utimes path when when (..any_callback write!) - node_fs)))) - - (~~ (template [<name> <method>] - [(def: (<name> data path) - (with_async write! (Try Any) - (<method> path (Buffer::from data) (..any_callback write!) - node_fs)))] - - [write Fs::writeFile] - [append Fs::appendFile] - )) - - (def: (move destination origin) - (with_async write! (Try Any) - (Fs::rename origin destination (..any_callback write!) - node_fs)))))))))) + (~~ (template [<name> <method>] + [(def: (<name> data path) + (with_async write! (Try Any) + (<method> path (Buffer::from data) (..any_callback write!) + node_fs)))] + + [write Fs::writeFile] + [append Fs::appendFile] + )) + + (def: (move destination origin) + (with_async write! (Try Any) + (Fs::rename origin destination (..any_callback write!) + node_fs)))))))))) @.python (as_is (type: (Tuple/2 left right) @@ -699,8 +699,8 @@ output (loop [input (|> children (array.list {.#None}) (list#each (|>> (format path ..ruby_separator)))) - output (: (List ..Path) - (list))] + output (is (List ..Path) + (list))] (case input {.#End} (in output) @@ -824,7 +824,7 @@ ... [(def: (<name> data) ... (do [! (try.with io.monad)] ... [outcome (..file_put_contents [path ("php pack" ..byte_array_format data) <mode>])] - ... (if (bit#= false (:as Bit outcome)) + ... (if (bit#= false (as Bit outcome)) ... (# io.monad in (exception.except ..cannot_write_to_file [path])) ... (in []))))] @@ -835,7 +835,7 @@ ... (def: (content _) ... (do [! (try.with io.monad)] ... [data (..file_get_contents [path])] - ... (if (bit#= false (:as Bit data)) + ... (if (bit#= false (as Bit data)) ... (# io.monad in (exception.except ..cannot_find_file [path])) ... (in (..unpack [..byte_array_format data]))))) @@ -846,7 +846,7 @@ ... [(def: (<name> _) ... (do [! (try.with io.monad)] ... [value (<ffi> [path])] - ... (if (bit#= false (:as Bit value)) + ... (if (bit#= false (as Bit value)) ... (# io.monad in (exception.except ..cannot_find_file [path])) ... (in (`` (|> value (~~ (template.spliced <pipeline>))))))))] @@ -860,21 +860,21 @@ ... (def: (modify moment) ... (do [! (try.with io.monad)] ... [verdict (..touch [path (|> moment instant.relative duration.millis (i./ +1,000))])] - ... (if (bit#= false (:as Bit verdict)) + ... (if (bit#= false (as Bit verdict)) ... (# io.monad in (exception.except ..cannot_find_file [path])) ... (in [])))) ... (def: (move destination) ... (do [! (try.with io.monad)] ... [verdict (..rename [path destination])] - ... (if (bit#= false (:as Bit verdict)) + ... (if (bit#= false (as Bit verdict)) ... (# io.monad in (exception.except ..cannot_find_file [path])) ... (in (file destination))))) ... (def: (delete _) ... (do (try.with io.monad) ... [verdict (..unlink [path])] - ... (if (bit#= false (:as Bit verdict)) + ... (if (bit#= false (as Bit verdict)) ... (# io.monad in (exception.except ..cannot_find_file [path])) ... (in [])))) ... )) @@ -894,7 +894,7 @@ ... (list.only (function (_ child) ... (not (or (text#= "." child) ... (text#= ".." child)))))) - ... output (: (List (<capability> IO)) + ... output (is (List (<capability> IO)) ... (list))] ... (case input ... {.#End} @@ -914,7 +914,7 @@ ... (def: (discard _) ... (do (try.with io.monad) ... [verdict (..rmdir [path])] - ... (if (bit#= false (:as Bit verdict)) + ... (if (bit#= false (as Bit verdict)) ... (# io.monad in (exception.except ..cannot_find_directory [path])) ... (in [])))) ... )) diff --git a/stdlib/source/library/lux/world/file/watch.lux b/stdlib/source/library/lux/world/file/watch.lux index 8b100638b..645c4e99e 100644 --- a/stdlib/source/library/lux/world/file/watch.lux +++ b/stdlib/source/library/lux/world/file/watch.lux @@ -29,7 +29,7 @@ [time ["[0]" instant {"+" Instant} ("[1]#[0]" equivalence)]] [type - [abstract {"+" abstract: :representation :abstraction}]]]] + [abstract {"+" abstract: representation abstraction}]]]] ["[0]" //]) (abstract: .public Concern @@ -40,7 +40,7 @@ (def: none Concern - (:abstraction + (abstraction [#creation false #modification false #deletion false])) @@ -48,14 +48,14 @@ (template [<concern> <predicate> <event> <create> <modify> <delete>] [(def: .public <concern> Concern - (:abstraction + (abstraction [#creation <create> #modification <modify> #deletion <delete>])) (def: .public <predicate> (Predicate Concern) - (|>> :representation (the <event>)))] + (|>> representation (the <event>)))] [creation creation? #creation true false false] @@ -67,7 +67,7 @@ (def: .public (also left right) (-> Concern Concern Concern) - (:abstraction + (abstraction [#creation (or (..creation? left) (..creation? right)) #modification (or (..modification? left) (..modification? right)) #deletion (or (..deletion? left) (..deletion? right))])) @@ -83,14 +83,14 @@ (type: .public (Watcher !) (Interface - (: (-> Concern //.Path (! (Try Any))) - start) - (: (-> //.Path (! (Try Concern))) - concern) - (: (-> //.Path (! (Try Concern))) - stop) - (: (-> [] (! (Try (List [Concern //.Path])))) - poll))) + (is (-> Concern //.Path (! (Try Any))) + start) + (is (-> //.Path (! (Try Concern))) + concern) + (is (-> //.Path (! (Try Concern))) + stop) + (is (-> [] (! (Try (List [Concern //.Path])))) + poll))) (template [<name>] [(exception: .public (<name> [path //.Path]) @@ -129,8 +129,8 @@ (do ! [last_modified (# fs last_modified file)] (in (dictionary.has file last_modified tracker)))) - (: File_Tracker - (dictionary.empty text.hash)) + (is File_Tracker + (dictionary.empty text.hash)) files))) (def: (available_files fs directory) @@ -186,8 +186,8 @@ (def: .public (polling fs) (-> (//.System Async) (Watcher Async)) - (let [tracker (: (Var Directory_Tracker) - (stm.var (dictionary.empty text.hash)))] + (let [tracker (is (Var Directory_Tracker) + (stm.var (dictionary.empty text.hash)))] (implementation (def: (start new_concern path) (do [! async.monad] @@ -308,8 +308,8 @@ (def: (default_event_concern event) (All (_ a) (-> (java/nio/file/WatchEvent a) Concern)) - (let [kind (:as (java/nio/file/WatchEvent$Kind java/nio/file/Path) - (java/nio/file/WatchEvent::kind event))] + (let [kind (as (java/nio/file/WatchEvent$Kind java/nio/file/Path) + (java/nio/file/WatchEvent::kind event))] (cond (same? (java/nio/file/StandardWatchEventKinds::ENTRY_CREATE) kind) ..creation @@ -374,8 +374,8 @@ (def: (default_poll watcher) (-> java/nio/file/WatchService (IO (Try (List [Concern //.Path])))) - (loop [output (: (List [Concern //.Path]) - (list))] + (loop [output (is (List [Concern //.Path]) + (list))] (do (try.with io.monad) [?key (java/nio/file/WatchService::poll watcher)] (case ?key @@ -386,10 +386,10 @@ (do ! [.let [path (|> key java/nio/file/WatchKey::watchable - (:as java/nio/file/Path) + (as java/nio/file/Path) java/nio/file/Path::toString ffi.of_string - (:as //.Path))] + (as //.Path))] the_concern (..default_key_concern key)] (again {.#Item [the_concern path] output})) @@ -402,13 +402,13 @@ (-> Concern (List Watch_Event)) ($_ list#composite (if (..creation? concern) - (list (:as Watch_Event (java/nio/file/StandardWatchEventKinds::ENTRY_CREATE))) + (list (as Watch_Event (java/nio/file/StandardWatchEventKinds::ENTRY_CREATE))) (list)) (if (..modification? concern) - (list (:as Watch_Event (java/nio/file/StandardWatchEventKinds::ENTRY_MODIFY))) + (list (as Watch_Event (java/nio/file/StandardWatchEventKinds::ENTRY_MODIFY))) (list)) (if (..deletion? concern) - (list (:as Watch_Event (java/nio/file/StandardWatchEventKinds::ENTRY_DELETE))) + (list (as Watch_Event (java/nio/file/StandardWatchEventKinds::ENTRY_DELETE))) (list)) )) @@ -417,49 +417,49 @@ (do (try.with io.monad) [watcher (java/nio/file/FileSystem::newWatchService (java/nio/file/FileSystems::getDefault)) - .let [tracker (stm.var (: (Dictionary //.Path [Concern java/nio/file/WatchKey]) - (dictionary.empty text.hash))) - - stop (: (-> //.Path (Async (Try Concern))) - (function (_ path) - (do [! async.monad] - [@tracker (stm.commit! (stm.read tracker))] - (case (dictionary.value path @tracker) - {.#Some [the_concern key]} - (do ! - [_ (async.future - (java/nio/file/WatchKey::cancel key)) - _ (stm.commit! (stm.update (dictionary.lacks path) tracker))] - (in {try.#Success the_concern})) - - {.#None} - (in (exception.except ..not_being_watched [path]))))))]] - (in (: (Watcher Async) - (implementation - (def: (start the_concern path) - (do async.monad - [?concern (stop path)] - (do (try.with async.monad) - [key (..default_start (..watch_events (..also (try.else ..none ?concern) - the_concern)) - watcher - path)] - (do async.monad - [_ (stm.commit! (stm.update (dictionary.has path [the_concern key]) tracker))] - (in {try.#Success []}))))) - (def: (concern path) - (do async.monad - [@tracker (stm.commit! (stm.read tracker))] - (case (dictionary.value path @tracker) - {.#Some [it key]} - (in {try.#Success it}) - - {.#None} - (in (exception.except ..not_being_watched [path]))))) - (def: stop stop) - (def: (poll _) - (async.future (..default_poll watcher))) - ))))) + .let [tracker (stm.var (is (Dictionary //.Path [Concern java/nio/file/WatchKey]) + (dictionary.empty text.hash))) + + stop (is (-> //.Path (Async (Try Concern))) + (function (_ path) + (do [! async.monad] + [@tracker (stm.commit! (stm.read tracker))] + (case (dictionary.value path @tracker) + {.#Some [the_concern key]} + (do ! + [_ (async.future + (java/nio/file/WatchKey::cancel key)) + _ (stm.commit! (stm.update (dictionary.lacks path) tracker))] + (in {try.#Success the_concern})) + + {.#None} + (in (exception.except ..not_being_watched [path]))))))]] + (in (is (Watcher Async) + (implementation + (def: (start the_concern path) + (do async.monad + [?concern (stop path)] + (do (try.with async.monad) + [key (..default_start (..watch_events (..also (try.else ..none ?concern) + the_concern)) + watcher + path)] + (do async.monad + [_ (stm.commit! (stm.update (dictionary.has path [the_concern key]) tracker))] + (in {try.#Success []}))))) + (def: (concern path) + (do async.monad + [@tracker (stm.commit! (stm.read tracker))] + (case (dictionary.value path @tracker) + {.#Some [it key]} + (in {try.#Success it}) + + {.#None} + (in (exception.except ..not_being_watched [path]))))) + (def: stop stop) + (def: (poll _) + (async.future (..default_poll watcher))) + ))))) )] (for @.old (as_is <jvm>) @.jvm (as_is <jvm>) diff --git a/stdlib/source/library/lux/world/net/http/client.lux b/stdlib/source/library/lux/world/net/http/client.lux index 6ad98c38c..4702436f2 100644 --- a/stdlib/source/library/lux/world/net/http/client.lux +++ b/stdlib/source/library/lux/world/net/http/client.lux @@ -32,9 +32,9 @@ (type: .public (Client !) (Interface - (: (-> //.Method URL //.Headers (Maybe Binary) - (! (Try (//.Response !)))) - request))) + (is (-> //.Method URL //.Headers (Maybe Binary) + (! (Try (//.Response !)))) + request))) (syntax: (method_function [[_ name] <code>.symbol]) (in (list (code.local_symbol (text.replaced "#" "" (text.lower_cased name)))))) @@ -191,34 +191,34 @@ (Client IO) (def: (request method url headers data) - (: (IO (Try (//.Response IO))) - (do [! (try.with io.monad)] - [connection (|> url ffi.as_string java/net/URL::new java/net/URL::openConnection) - .let [connection (:as java/net/HttpURLConnection connection)] - _ (java/net/HttpURLConnection::setRequestMethod (ffi.as_string (..jvm_method method)) connection) - _ (monad.each ! (function (_ [name value]) - (java/net/URLConnection::setRequestProperty (ffi.as_string name) (ffi.as_string value) connection)) - (dictionary.entries headers)) - _ (case data - {.#Some data} - (do ! - [_ (java/net/URLConnection::setDoOutput true connection) - stream (java/net/URLConnection::getOutputStream connection) - _ (java/io/OutputStream::write data stream) - _ (java/io/OutputStream::flush stream) - _ (java/lang/AutoCloseable::close stream)] - (in [])) - - {.#None} - (in [])) - status (java/net/HttpURLConnection::getResponseCode connection) - headers (..default_headers connection) - input (|> connection - java/net/URLConnection::getInputStream - (# ! each (|>> java/io/BufferedInputStream::new)))] - (in [(.nat (ffi.of_int status)) - [//.#headers headers - //.#body (..default_body input)]]))))))] + (is (IO (Try (//.Response IO))) + (do [! (try.with io.monad)] + [connection (|> url ffi.as_string java/net/URL::new java/net/URL::openConnection) + .let [connection (as java/net/HttpURLConnection connection)] + _ (java/net/HttpURLConnection::setRequestMethod (ffi.as_string (..jvm_method method)) connection) + _ (monad.each ! (function (_ [name value]) + (java/net/URLConnection::setRequestProperty (ffi.as_string name) (ffi.as_string value) connection)) + (dictionary.entries headers)) + _ (case data + {.#Some data} + (do ! + [_ (java/net/URLConnection::setDoOutput true connection) + stream (java/net/URLConnection::getOutputStream connection) + _ (java/io/OutputStream::write data stream) + _ (java/io/OutputStream::flush stream) + _ (java/lang/AutoCloseable::close stream)] + (in [])) + + {.#None} + (in [])) + status (java/net/HttpURLConnection::getResponseCode connection) + headers (..default_headers connection) + input (|> connection + java/net/URLConnection::getInputStream + (# ! each (|>> java/io/BufferedInputStream::new)))] + (in [(.nat (ffi.of_int status)) + [//.#headers headers + //.#body (..default_body input)]]))))))] (for @.old (as_is <jvm>) @.jvm (as_is <jvm>) (as_is))) @@ -232,9 +232,9 @@ (# async.monad each (|>> (pipe.case {try.#Success [status message]} - {try.#Success [status (revised //.#body (: (-> (//.Body IO) (//.Body Async)) - (function (_ body) - (|>> body async.future))) + {try.#Success [status (revised //.#body (is (-> (//.Body IO) (//.Body Async)) + (function (_ body) + (|>> body async.future))) message)]} {try.#Failure error} diff --git a/stdlib/source/library/lux/world/net/http/mime.lux b/stdlib/source/library/lux/world/net/http/mime.lux index 531173176..b9e9b8505 100644 --- a/stdlib/source/library/lux/world/net/http/mime.lux +++ b/stdlib/source/library/lux/world/net/http/mime.lux @@ -1,23 +1,23 @@ (.using - [library - [lux "*" - [data - ["[0]" text - ["%" format {"+" format}] - ["[0]" encoding {"+" Encoding}]]] - [type - abstract]]]) + [library + [lux "*" + [data + ["[0]" text + ["%" format {"+" format}] + ["[0]" encoding {"+" Encoding}]]] + [type + [abstract {"-" pattern}]]]]) (abstract: .public MIME Text (def: .public mime (-> Text MIME) - (|>> :abstraction)) + (|>> abstraction)) (def: .public name (-> MIME Text) - (|>> :representation)) + (|>> representation)) ) ... https://developer.mozilla.org/en-US/docs/Web/HTTP/Basics_of_HTTP/MIME_types/Complete_list_of_MIME_types diff --git a/stdlib/source/library/lux/world/program.lux b/stdlib/source/library/lux/world/program.lux index 2da3bad68..9bdba0392 100644 --- a/stdlib/source/library/lux/world/program.lux +++ b/stdlib/source/library/lux/world/program.lux @@ -31,9 +31,7 @@ ["[0]" template]] [math [number - ["i" int]]] - [type - abstract]]] + ["i" int]]]]] [// [file {"+" Path}] [shell {"+" Exit}]]))) @@ -44,16 +42,16 @@ (type: .public (Program !) (Interface - (: (-> Any (! (List Text))) - available_variables) - (: (-> Text (! (Try Text))) - variable) - (: Path - home) - (: Path - directory) - (: (-> Exit (! Nothing)) - exit))) + (is (-> Any (! (List Text))) + available_variables) + (is (-> Text (! (Try Text))) + variable) + (is Path + home) + (is Path + directory) + (is (-> Exit (! Nothing)) + exit))) (def: .public (environment monad program) (All (_ !) (-> (Monad !) (Program !) (! Environment))) @@ -317,7 +315,7 @@ ... ..array_keys ... (array.list {.#None}) ... (list#each (function (_ variable) - ... [variable ("php array read" (:as Nat variable) environment)])) + ... [variable ("php array read" (as Nat variable) environment)])) ... (dictionary.of_list text.hash)))) ... @.scheme (do io.monad ... [input (..get-environment-variables [])] @@ -346,8 +344,8 @@ @.js (io.io (if ffi.on_node_js? (case (do maybe.monad [process/env (ffi.global Object [process env])] - (array.read! (:as Nat name) - (:as (Array Text) process/env))) + (array.read! (as Nat name) + (as (Array Text) process/env))) {.#Some value} {try.#Success value} @@ -371,7 +369,7 @@ @.js (if ffi.on_node_js? (|> (node_js.require "os") maybe.trusted - (:as NodeJs_OS) + (as NodeJs_OS) NodeJs_OS::homedir) <default>) @.python (os/path::expanduser "~") @@ -379,7 +377,7 @@ @.ruby (io.io (Dir::home)) ... @.php (do io.monad ... [output (..getenv/1 ["HOME"])] - ... (in (if (bit#= false (:as Bit output)) + ... (in (if (bit#= false (as Bit output)) ... "~" ... output))) @@ -413,7 +411,7 @@ @.ruby (io.io (FileUtils::pwd)) ... @.php (do io.monad ... [output (..getcwd [])] - ... (in (if (bit#= false (:as Bit output)) + ... (in (if (bit#= false (as Bit output)) ... "." ... output))) diff --git a/stdlib/source/library/lux/world/shell.lux b/stdlib/source/library/lux/world/shell.lux index c9092ae35..1881054bd 100644 --- a/stdlib/source/library/lux/world/shell.lux +++ b/stdlib/source/library/lux/world/shell.lux @@ -47,16 +47,16 @@ (type: .public (Process !) (Interface - (: (-> [] (! (Try Text))) - read) - (: (-> [] (! (Try Text))) - fail) - (: (-> Text (! (Try Any))) - write) - (: (-> [] (! (Try Any))) - destroy) - (: (-> [] (! (Try Exit))) - await))) + (is (-> [] (! (Try Text))) + read) + (is (-> [] (! (Try Text))) + fail) + (is (-> Text (! (Try Any))) + write) + (is (-> [] (! (Try Any))) + destroy) + (is (-> [] (! (Try Exit))) + await))) (def: (async_process process) (-> (Process IO) (Process Async)) @@ -81,8 +81,8 @@ (type: .public (Shell !) (Interface - (: (-> [Environment Path Command (List Argument)] (! (Try (Process !)))) - execute))) + (is (-> [Environment Path Command (List Argument)] (! (Try (Process !)))) + execute))) (def: .public (async shell) (-> (Shell IO) (Shell Async)) @@ -96,12 +96,12 @@ ... https://en.wikipedia.org/wiki/Code_injection#Shell_injection (type: (Policy ?) (Interface - (: (-> Command (Safe Command ?)) - command) - (: (-> Argument (Safe Argument ?)) - argument) - (: (All (_ a) (-> (Safe a ?) a)) - value))) + (is (-> Command (Safe Command ?)) + command) + (is (-> Argument (Safe Argument ?)) + argument) + (is (All (_ a) (-> (Safe a ?) a)) + value))) (type: (Sanitizer a) (-> a a)) @@ -139,35 +139,35 @@ (def: (policy safe_command safe_argument) (Ex (_ ?) (-> (Sanitizer Command) (Sanitizer Argument) (Policy ?))) (?.with_policy - (: (Context Safety Policy) - (function (_ (open "?[0]")) - (implementation - (def: command (|>> safe_command ?#can_upgrade)) - (def: argument (|>> safe_argument ?#can_upgrade)) - (def: value ?#can_downgrade)))))) + (is (Context Safety Policy) + (function (_ (open "?[0]")) + (implementation + (def: command (|>> safe_command ?#can_upgrade)) + (def: argument (|>> safe_argument ?#can_upgrade)) + (def: value ?#can_downgrade)))))) (def: unix_policy - (let [replacer (: Replacer - (|>> (format "\"))) - safe_command (: (Sanitizer Command) - (..safe_common_command replacer)) - safe_argument (: (Sanitizer Argument) - (|>> (..replaced "'" replacer) - (text.enclosed' "'")))] + (let [replacer (is Replacer + (|>> (format "\"))) + safe_command (is (Sanitizer Command) + (..safe_common_command replacer)) + safe_argument (is (Sanitizer Argument) + (|>> (..replaced "'" replacer) + (text.enclosed' "'")))] (..policy safe_command safe_argument))) (def: windows_policy - (let [replacer (: Replacer - (function.constant " ")) - safe_command (: (Sanitizer Command) - (|>> (..safe_common_command replacer) - (..replaced "%" replacer) - (..replaced "!" replacer))) - safe_argument (: (Sanitizer Argument) - (|>> (..replaced "%" replacer) - (..replaced "!" replacer) - (..replaced text.double_quote replacer) - (text.enclosed' text.double_quote)))] + (let [replacer (is Replacer + (function.constant " ")) + safe_command (is (Sanitizer Command) + (|>> (..safe_common_command replacer) + (..replaced "%" replacer) + (..replaced "!" replacer))) + safe_argument (is (Sanitizer Argument) + (|>> (..replaced "%" replacer) + (..replaced "!" replacer) + (..replaced text.double_quote replacer) + (text.enclosed' text.double_quote)))] (..policy safe_command safe_argument))) (with_expansions [<jvm> (as_is (import: java/lang/String @@ -194,8 +194,8 @@ (java/util/Map java/lang/String java/lang/String)) (list#mix (function (_ [key value] target') (exec - (java/util/Map::put (:as java/lang/String key) - (:as java/lang/String value) + (java/util/Map::put (as java/lang/String key) + (as java/lang/String value) target') target')) target @@ -243,31 +243,31 @@ jvm_error (|> jvm_error java/io/InputStreamReader::new java/io/BufferedReader::new)]] - (in (: (Process IO) - (`` (implementation - (~~ (template [<name> <stream>] - [(def: (<name> _) - (do ! - [output (java/io/BufferedReader::readLine <stream>)] - (case output - {.#Some output} - (in (ffi.of_string output)) - - {.#None} - (# io.monad in (exception.except ..no_more_output [])))))] - - [read jvm_input] - [fail jvm_error] - )) - (def: (write message) - (java/io/OutputStream::write (# utf8.codec encoded message) jvm_output)) - (~~ (template [<name> <method>] - [(def: (<name> _) - (|> process <method>))] - - [destroy java/lang/Process::destroy] - [await (<| (# ! each (|>> ffi.of_int)) java/lang/Process::waitFor)] - )))))))) + (in (is (Process IO) + (`` (implementation + (~~ (template [<name> <stream>] + [(def: (<name> _) + (do ! + [output (java/io/BufferedReader::readLine <stream>)] + (case output + {.#Some output} + (in (ffi.of_string output)) + + {.#None} + (# io.monad in (exception.except ..no_more_output [])))))] + + [read jvm_input] + [fail jvm_error] + )) + (def: (write message) + (java/io/OutputStream::write (# utf8.codec encoded message) jvm_output)) + (~~ (template [<name> <method>] + [(def: (<name> _) + (|> process <method>))] + + [destroy java/lang/Process::destroy] + [await (<| (# ! each (|>> ffi.of_int)) java/lang/Process::waitFor)] + )))))))) (import: java/io/File "[1]::[0]" @@ -313,16 +313,16 @@ (type: .public (Mock s) (Interface - (: (-> s (Try [s Text])) - on_read) - (: (-> s (Try [s Text])) - on_fail) - (: (-> Text s (Try s)) - on_write) - (: (-> s (Try s)) - on_destroy) - (: (-> s (Try [s Exit])) - on_await))) + (is (-> s (Try [s Text])) + on_read) + (is (-> s (Try [s Text])) + on_fail) + (is (-> Text s (Try s)) + on_write) + (is (-> s (Try s)) + on_destroy) + (is (-> s (Try [s Exit])) + on_await))) (`` (implementation: (mock_process state mock) (All (_ s) (-> (Atom s) (Mock s) (Process IO))) |