diff options
author | Eduardo Julian | 2021-09-08 18:57:27 -0400 |
---|---|---|
committer | Eduardo Julian | 2021-09-08 18:57:27 -0400 |
commit | 880cb37c261df20b7b8d968a909557bbc63d6b7f (patch) | |
tree | eb94b5572f3b03b855927c67e171b73ceb4db6c4 /stdlib/source/library/lux/tool/compiler | |
parent | 9ae7272d50b64dc9c8651e7a684abc007d4f2caf (diff) |
Normalized syntax of "exception:", "actor:" and "message:".
Diffstat (limited to 'stdlib/source/library/lux/tool/compiler')
28 files changed, 156 insertions, 96 deletions
diff --git a/stdlib/source/library/lux/tool/compiler/default/platform.lux b/stdlib/source/library/lux/tool/compiler/default/platform.lux index c2442dd78..be5d7df27 100644 --- a/stdlib/source/library/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/library/lux/tool/compiler/default/platform.lux @@ -357,18 +357,18 @@ (or (dependence? import (value@ #depends_on) module) (dependence? module (value@ #depended_by) import)))) - (exception: .public (module_cannot_import_itself {module Module}) + (exception: .public (module_cannot_import_itself [module Module]) (exception.report ["Module" (%.text module)])) - (exception: .public (cannot_import_circular_dependency {importer Module} - {importee Module}) + (exception: .public (cannot_import_circular_dependency [importer Module + importee Module]) (exception.report ["Importer" (%.text importer)] ["importee" (%.text importee)])) - (exception: .public (cannot_import_twice {importer Module} - {duplicates (Set Module)}) + (exception: .public (cannot_import_twice [importer Module + duplicates (Set Module)]) (exception.report ["Importer" (%.text importer)] ["Duplicates" (%.list %.text (set.list duplicates))])) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux index c0bc4a79e..0b9e317fe 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/analysis/macro.lux @@ -13,13 +13,17 @@ [///// ["[0]" phase]]) -(exception: .public (expansion_failed {macro Name} {inputs (List Code)} {error Text}) +(exception: .public (expansion_failed [macro Name + inputs (List Code) + error Text]) (exception.report ["Macro" (%.name macro)] ["Inputs" (exception.listing %.code inputs)] ["Error" error])) -(exception: .public (must_have_single_expansion {macro Name} {inputs (List Code)} {outputs (List Code)}) +(exception: .public (must_have_single_expansion [macro Name + inputs (List Code) + outputs (List Code)]) (exception.report ["Macro" (%.name macro)] ["Inputs" (exception.listing %.code inputs)] 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 efad246fd..7ed71e658 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/generation.lux @@ -36,12 +36,12 @@ (type: .public (Buffer directive) (Row [artifact.ID (Maybe Text) directive])) -(exception: .public (cannot_interpret {error Text}) +(exception: .public (cannot_interpret [error Text]) (exception.report ["Error" error])) (template [<name>] - [(exception: .public (<name> {artifact_id artifact.ID}) + [(exception: .public (<name> [artifact_id artifact.ID]) (exception.report ["Artifact ID" (%.nat artifact_id)]))] @@ -257,8 +257,8 @@ [learn_directive artifact.directive] ) -(exception: .public (unknown_definition {name Name} - {known_definitions (List Text)}) +(exception: .public (unknown_definition [name Name + known_definitions (List Text)]) (exception.report ["Definition" (name.short name)] ["Module" (name.module name)] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux index c7f8130fe..c8c2b9fd3 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis.lux @@ -28,7 +28,7 @@ [meta [archive {"+" [Archive]}]]]]]]) -(exception: .public (unrecognized_syntax {code Code}) +(exception: .public (unrecognized_syntax [code Code]) (exception.report ["Code" (%.code code)])) ... TODO: Had to split the 'compile' function due to compilation issues 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 fda27838d..ec8fb396e 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 @@ -34,29 +34,33 @@ [/// ["[1]" phase]]]]]]) -(exception: .public (cannot_match_with_pattern {type Type} {pattern Code}) +(exception: .public (cannot_match_with_pattern [type Type + pattern Code]) (exception.report ["Type" (%.type type)] ["Pattern" (%.code pattern)])) -(exception: .public (sum_has_no_case {case Nat} {type Type}) +(exception: .public (sum_has_no_case [case Nat + type Type]) (exception.report ["Case" (%.nat case)] ["Type" (%.type type)])) -(exception: .public (not_a_pattern {code Code}) +(exception: .public (not_a_pattern [code Code]) (exception.report ["Code" (%.code code)])) -(exception: .public (cannot_simplify_for_pattern_matching {type Type}) +(exception: .public (cannot_simplify_for_pattern_matching [type Type]) (exception.report ["Type" (%.type type)])) -(exception: .public (non_exhaustive_pattern_matching {input Code} {branches (List [Code Code])} {coverage Coverage}) +(exception: .public (non_exhaustive_pattern_matching [input Code + branches (List [Code Code]) + coverage Coverage]) (exception.report ["Input" (%.code input)] ["Branches" (%.code (code.record branches))] ["Coverage" (/coverage.%coverage coverage)])) -(exception: .public (cannot_have_empty_branches {message Text}) +(exception: .public (cannot_have_empty_branches [message Text]) message) (def: (re_quantify envs baseT) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux index 8427dd68b..5dcedd669 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/case/coverage.lux @@ -24,7 +24,7 @@ [/// ["[1]" phase ("[1]\[0]" monad)]]]]) -(exception: .public (invalid_tuple_pattern) +(exception: .public invalid_tuple_pattern "Tuple size must be >= 2") (def: cases @@ -167,7 +167,8 @@ ... always be a pattern prior to them that would match the input. ... Because of that, the presence of redundant patterns is assumed to ... be a bug, likely due to programmer carelessness. -(exception: .public (redundant_pattern {so_far Coverage} {addition Coverage}) +(exception: .public (redundant_pattern [so_far Coverage + addition Coverage]) (exception.report ["Coverage so-far" (%coverage so_far)] ["Coverage addition" (%coverage addition)])) @@ -212,7 +213,8 @@ (open: "coverage/[0]" ..equivalence) -(exception: .public (variants_do_not_match {addition_cases Nat} {so_far_cases Nat}) +(exception: .public (variants_do_not_match [addition_cases Nat + so_far_cases Nat]) (exception.report ["So-far Cases" (%.nat so_far_cases)] ["Addition Cases" (%.nat addition_cases)])) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux index 7574d89aa..fe0a32584 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/function.lux @@ -27,13 +27,18 @@ [reference {"+" []} [variable {"+" []}]]]]]]) -(exception: .public (cannot_analyse {expected Type} {function Text} {argument Text} {body Code}) +(exception: .public (cannot_analyse [expected Type + function Text + argument Text + body Code]) (ex.report ["Type" (%.type expected)] ["Function" function] ["Argument" argument] ["Body" (%.code body)])) -(exception: .public (cannot_apply {functionT Type} {functionC Code} {arguments (List Code)}) +(exception: .public (cannot_apply [functionT Type + functionC Code + arguments (List Code)]) (ex.report ["Function type" (%.type functionT)] ["Function" (%.code functionC)] ["Arguments" (|> arguments diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux index 96d5b870e..b6d610a7f 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/inference.lux @@ -28,29 +28,34 @@ [meta [archive {"+" [Archive]}]]]]]]) -(exception: .public (variant_tag_out_of_bounds {size Nat} {tag Tag} {type Type}) +(exception: .public (variant_tag_out_of_bounds [size Nat + tag Tag + type Type]) (exception.report ["Tag" (%.nat tag)] ["Variant size" (%.int (.int size))] ["Variant type" (%.type type)])) -(exception: .public (cannot_infer {type Type} {args (List Code)}) +(exception: .public (cannot_infer [type Type + args (List Code)]) (exception.report ["Type" (%.type type)] ["Arguments" (exception.listing %.code args)])) -(exception: .public (cannot_infer_argument {inferred Type} {argument Code}) +(exception: .public (cannot_infer_argument [inferred Type + argument Code]) (exception.report ["Inferred Type" (%.type inferred)] ["Argument" (%.code argument)])) -(exception: .public (smaller_variant_than_expected {expected Nat} {actual Nat}) +(exception: .public (smaller_variant_than_expected [expected Nat + actual Nat]) (exception.report ["Expected" (%.int (.int expected))] ["Actual" (%.int (.int actual))])) (template [<name>] - [(exception: .public (<name> {type Type}) + [(exception: .public (<name> [type Type]) (%.type type))] [not_a_variant_type] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux index 845d07f17..31ace4429 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/module.lux @@ -24,12 +24,13 @@ (type: .public Tag Text) -(exception: .public (unknown_module {module Text}) +(exception: .public (unknown_module [module Text]) (exception.report ["Module" module])) (template [<name>] - [(exception: .public (<name> {tags (List Text)} {owner Type}) + [(exception: .public (<name> [tags (List Text) + owner Type]) (exception.report ["Tags" (text.interposed " " tags)] ["Type" (%.type owner)]))] @@ -38,7 +39,8 @@ [cannot_declare_tags_for_foreign_type] ) -(exception: .public (cannot_define_more_than_once {name Name} {already_existing Global}) +(exception: .public (cannot_define_more_than_once [name Name + already_existing Global]) (exception.report ["Definition" (%.name name)] ["Original" (case already_existing @@ -57,7 +59,8 @@ (#.Slot _) (format "slot " (%.name name)))])) -(exception: .public (can_only_change_state_of_active_module {module Text} {state Module_State}) +(exception: .public (can_only_change_state_of_active_module [module Text + state Module_State]) (exception.report ["Module" module] ["Desired state" (case state diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux index 33b1c7e32..f3bc9d282 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/reference.lux @@ -20,16 +20,17 @@ ["[1][0]" reference] ["[1]" phase]]]]]) -(exception: .public (foreign_module_has_not_been_imported {current Text} {foreign Text}) +(exception: .public (foreign_module_has_not_been_imported [current Text + foreign Text]) (exception.report ["Current" current] ["Foreign" foreign])) -(exception: .public (definition_has_not_been_exported {definition Name}) +(exception: .public (definition_has_not_been_exported [definition Name]) (exception.report ["Definition" (%.name definition)])) -(exception: .public (labels_are_not_definitions {definition Name}) +(exception: .public (labels_are_not_definitions [definition Name]) (exception.report ["Label" (%.name definition)])) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux index 3c18c178b..f6c226e9a 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/analysis/structure.lux @@ -37,14 +37,17 @@ [meta [archive {"+" [Archive]}]]]]]]) -(exception: .public (invalid_variant_type {type Type} {tag Tag} {code Code}) +(exception: .public (invalid_variant_type [type Type + tag Tag + code Code]) (exception.report ["Type" (%.type type)] ["Tag" (%.nat tag)] ["Expression" (%.code code)])) (template [<name>] - [(exception: .public (<name> {type Type} {members (List Code)}) + [(exception: .public (<name> [type Type + members (List Code)]) (exception.report ["Type" (%.type type)] ["Expression" (%.code (` [(~+ members)]))]))] @@ -53,11 +56,13 @@ [cannot_analyse_tuple] ) -(exception: .public (not_a_quantified_type {type Type}) +(exception: .public (not_a_quantified_type [type Type]) (%.type type)) (template [<name>] - [(exception: .public (<name> {type Type} {tag Tag} {code Code}) + [(exception: .public (<name> [type Type + tag Tag + code Code]) (exception.report ["Type" (%.type type)] ["Tag" (%.nat tag)] @@ -68,7 +73,8 @@ ) (template [<name>] - [(exception: .public (<name> {key Name} {record (List [Name Code])}) + [(exception: .public (<name> [key Name + record (List [Name Code])]) (exception.report ["Tag" (%.code (code.tag key))] ["Record" (%.code (code.record (list\each (function (_ [keyI valC]) @@ -78,12 +84,16 @@ [cannot_repeat_tag] ) -(exception: .public (slot_does_not_belong_to_record {key Name} {type Type}) +(exception: .public (slot_does_not_belong_to_record [key Name + type Type]) (exception.report ["Tag" (%.code (code.tag key))] ["Type" (%.type type)])) -(exception: .public (record_size_mismatch {expected Nat} {actual Nat} {type Type} {record (List [Name Code])}) +(exception: .public (record_size_mismatch [expected Nat + actual Nat + type Type + record (List [Name Code])]) (exception.report ["Expected" (%.nat expected)] ["Actual" (%.nat actual)] 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 7a42fbb7e..3d3163553 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 @@ -28,15 +28,15 @@ [meta [archive {"+" [Archive]}]]]]]) -(exception: .public (not_a_directive {code Code}) +(exception: .public (not_a_directive [code Code]) (exception.report ["Directive" (%.code code)])) -(exception: .public (invalid_macro_call {code Code}) +(exception: .public (invalid_macro_call [code Code]) (exception.report ["Code" (%.code code)])) -(exception: .public (macro_was_not_found {name Name}) +(exception: .public (macro_was_not_found [name Name]) (exception.report ["Name" (%.name name)])) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux index 637c7e0a6..d54049e4e 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension.lux @@ -61,22 +61,27 @@ (type: .public (Phase s i o) (//.Phase (State s i o) i o)) -(exception: .public (cannot_overwrite {name Name}) +(exception: .public (cannot_overwrite [name Name]) (exception.report ["Extension" (%.text name)])) -(exception: .public (incorrect_arity {name Name} {arity Nat} {args Nat}) +(exception: .public (incorrect_arity [name Name + arity Nat + args Nat]) (exception.report ["Extension" (%.text name)] ["Expected" (%.nat arity)] ["Actual" (%.nat args)])) -(exception: .public [a] (invalid_syntax {name Name} {%format (Format a)} {inputs (List a)}) +(exception: .public [a] (invalid_syntax [name Name + %format (Format a) + inputs (List a)]) (exception.report ["Extension" (%.text name)] ["Inputs" (exception.listing %format inputs)])) -(exception: .public [s i o] (unknown {name Name} {bundle (Bundle s i o)}) +(exception: .public [s i o] (unknown [name Name + bundle (Bundle s i o)]) (exception.report ["Extension" (%.text name)] ["Available" (|> bundle 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 8591286fb..9ea592c20 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 @@ -115,7 +115,8 @@ (getDeclaredAnnotations [] [java/lang/annotation/Annotation])]) (template [<name>] - [(exception: .public (<name> {class External} {field Text}) + [(exception: .public (<name> [class External + field Text]) (exception.report ["Class" (%.text class)] ["Field" (%.text field)]))] @@ -124,13 +125,15 @@ [deprecated_field] ) -(exception: .public (deprecated_method {class External} {method Text} {type .Type}) +(exception: .public (deprecated_method [class External + method Text + type .Type]) (exception.report ["Class" (%.text class)] ["Method" (%.text method)] ["Type" (%.type type)])) -(exception: .public (deprecated_class {class External}) +(exception: .public (deprecated_class [class External]) (exception.report ["Class" (%.text class)])) @@ -204,7 +207,7 @@ #exceptions (List .Type)])) (template [<name>] - [(exception: .public (<name> {type .Type}) + [(exception: .public (<name> [type .Type]) (exception.report ["Type" (%.type type)]))] @@ -215,7 +218,7 @@ ) (template [<name>] - [(exception: .public (<name> {class External}) + [(exception: .public (<name> [class External]) (exception.report ["Class/type" (%.text class)]))] @@ -225,10 +228,10 @@ ) (template [<name>] - [(exception: .public (<name> {class External} - {method Text} - {inputsJT (List (Type Value))} - {hints (List Method_Signature)}) + [(exception: .public (<name> [class External + method Text + inputsJT (List (Type Value)) + hints (List Method_Signature)]) (exception.report ["Class" class] ["Method" method] @@ -239,14 +242,16 @@ [too_many_candidates] ) -(exception: .public (cannot_cast {from .Type} {to .Type} {value Code}) +(exception: .public (cannot_cast [from .Type + to .Type + value Code]) (exception.report ["From" (%.type from)] ["To" (%.type to)] ["Value" (%.code value)])) (template [<name>] - [(exception: .public (<name> {message Text}) + [(exception: .public (<name> [message Text]) message)] [primitives_cannot_have_type_parameters] @@ -1589,7 +1594,7 @@ ) (template [<name>] - [(exception: .public (<name> {methods (List [Text (Type Method)])}) + [(exception: .public (<name> [methods (List [Text (Type Method)])]) (exception.report ["Methods" (exception.listing (function (_ [name type]) @@ -1889,12 +1894,15 @@ <code>.any ))) -(exception: .public (unknown_super {name Text} {supers (List (Type Class))}) +(exception: .public (unknown_super [name Text + supers (List (Type Class))]) (exception.report ["Name" (%.text name)] ["Available" (exception.listing (|>> jvm_parser.read_class product.left) supers)])) -(exception: .public (mismatched_super_parameters {name Text} {expected Nat} {actual Nat}) +(exception: .public (mismatched_super_parameters [name Text + expected Nat + actual Nat]) (exception.report ["Name" (%.text name)] ["Expected" (%.nat expected)] @@ -2052,8 +2060,8 @@ not)) sub_set)) -(exception: .public (class_parameter_mismatch {expected (List Text)} - {actual (List (Type Parameter))}) +(exception: .public (class_parameter_mismatch [expected (List Text) + actual (List (Type Parameter))]) (exception.report ["Expected (amount)" (%.nat (list.size expected))] ["Expected (parameters)" (exception.listing %.text expected)] 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 a8e9ae29f..fb283bf9e 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 @@ -81,7 +81,7 @@ ... TODO: Get rid of this ASAP (as_is - (exception: .public (char_text_must_be_size_1 {text Text}) + (exception: .public (char_text_must_be_size_1 [text Text]) (exception.report ["Text" (%.text text)])) @@ -199,7 +199,7 @@ (typeA.with_type input (phase archive valueC))))])) -(exception: .public (not_a_type {symbol Name}) +(exception: .public (not_a_type [symbol Name]) (exception.report ["Symbol" (%.name symbol)])) 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 1da688392..0ebdde096 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 @@ -305,13 +305,16 @@ (in [#/////directive.imports imports #/////directive.referrals (list)])))])) -(exception: .public (cannot_alias_an_alias {local Alias} {foreign Alias} {target Name}) +(exception: .public (cannot_alias_an_alias [local Alias + foreign Alias + target Name]) (exception.report ["Local alias" (%.name local)] ["Foreign alias" (%.name foreign)] ["Target definition" (%.name target)])) -(exception: .public (cannot_alias_a_label {local Alias} {foreign Alias}) +(exception: .public (cannot_alias_a_label [local Alias + foreign Alias]) (exception.report ["Alias" (%.name local)] ["Label" (%.name foreign)])) 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 ac5f0fce9..e0626e0b6 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 @@ -330,7 +330,7 @@ [return Return parser.return] ) -(exception: .public (not_an_object_array {arrayJT (Type Array)}) +(exception: .public (not_an_object_array [arrayJT (Type Array)]) (exception.report ["JVM Type" (|> arrayJT type.signature signature.signature)])) 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 df781631c..6e5030da6 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 @@ -60,18 +60,21 @@ (def: init::type (type.method [(list) type.void (list)])) (def: init::modifier ($_ modifier\composite method.public method.static method.strict)) -(exception: .public (cannot_load {class Text} {error Text}) +(exception: .public (cannot_load [class Text + error Text]) (exception.report ["Class" class] ["Error" error])) -(exception: .public (invalid_field {class Text} {field Text} {error Text}) +(exception: .public (invalid_field [class Text + field Text + error Text]) (exception.report ["Class" class] ["Field" field] ["Error" error])) -(exception: .public (invalid_value {class Text}) +(exception: .public (invalid_value [class Text]) (exception.report ["Class" class])) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux index 3b820934f..4b9ef22e4 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/r/procedure/common.lux @@ -113,7 +113,7 @@ Unary (runtimeT.lux//try riskyO)) -(exception: .public (Wrong_Syntax {message Text}) +(exception: .public (Wrong_Syntax [message Text]) message) (def: .public (wrong_syntax procedure args) 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 316a1bed0..96139976a 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 @@ -27,7 +27,8 @@ ["[1]/[0]" variable {"+" [Register Variable]}]] ["[0]" phase ("[1]\[0]" monad)]]]]) -(exception: .public (cannot_find_foreign_variable_in_environment {foreign Register} {environment (Environment Synthesis)}) +(exception: .public (cannot_find_foreign_variable_in_environment [foreign Register + environment (Environment Synthesis)]) (exception.report ["Foreign" (%.nat foreign)] ["Environment" (exception.listing /.%synthesis environment)])) 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 afa30d83c..91e229d1a 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 @@ -209,7 +209,7 @@ (#.Item head tail)]))))) (template [<name>] - [(exception: .public (<name> {register Register}) + [(exception: .public (<name> [register Register]) (exception.report ["Register" (%.nat register)]))] diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/program.lux b/stdlib/source/library/lux/tool/compiler/language/lux/program.lux index ecafe7615..f085683fc 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/program.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/program.lux @@ -28,7 +28,7 @@ Text "") -(exception: .public (cannot_find_program {modules (List Module)}) +(exception: .public (cannot_find_program [modules (List Module)]) (exception.report ["Modules" (exception.listing %.text modules)])) 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 a04571b5b..3df8bb802 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/syntax.lux @@ -144,7 +144,7 @@ ["." name_separator] ) -(exception: .public (end_of_file {module Text}) +(exception: .public (end_of_file [module Text]) (exception.report ["Module" (%.text module)])) @@ -155,7 +155,10 @@ (let [end (|> start (!n/+ amount_of_input_shown) (n.min ("lux text size" input)))] (!clip start end input))) -(exception: .public (unrecognized_input {[file line column] Location} {context Text} {input Text} {offset Offset}) +(exception: .public (unrecognized_input [[file line column] Location + context Text + input Text + offset Offset]) (exception.report ["File" file] ["Line" (%.nat line)] @@ -163,7 +166,7 @@ ["Context" (%.text context)] ["Input" (input_at offset input)])) -(exception: .public (text_cannot_contain_new_lines {text Text}) +(exception: .public (text_cannot_contain_new_lines [text Text]) (exception.report ["Text" (%.text text)])) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive.lux b/stdlib/source/library/lux/tool/compiler/meta/archive.lux index d57f4a08b..d7d2fe237 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive.lux @@ -41,29 +41,29 @@ (type: .public Output (Row [artifact.ID (Maybe Text) Binary])) -(exception: .public (unknown_document {module Module} - {known_modules (List Module)}) +(exception: .public (unknown_document [module Module + known_modules (List Module)]) (exception.report ["Module" (%.text module)] ["Known Modules" (exception.listing %.text known_modules)])) -(exception: .public (cannot_replace_document {module Module} - {old (Document Any)} - {new (Document Any)}) +(exception: .public (cannot_replace_document [module Module + old (Document Any) + new (Document Any)]) (exception.report ["Module" (%.text module)] ["Old key" (signature.description (document.signature old))] ["New key" (signature.description (document.signature new))])) -(exception: .public (module_has_already_been_reserved {module Module}) +(exception: .public (module_has_already_been_reserved [module Module]) (exception.report ["Module" (%.text module)])) -(exception: .public (module_must_be_reserved_before_it_can_be_added {module Module}) +(exception: .public (module_must_be_reserved_before_it_can_be_added [module Module]) (exception.report ["Module" (%.text module)])) -(exception: .public (module_is_only_reserved {module Module}) +(exception: .public (module_is_only_reserved [module Module]) (exception.report ["Module" (%.text module)])) @@ -240,7 +240,8 @@ [version next] (binary.result ..writer)))) - (exception: .public (version_mismatch {expected Version} {actual Version}) + (exception: .public (version_mismatch [expected Version + actual Version]) (exception.report ["Expected" (%.nat expected)] ["Actual" (%.nat actual)])) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux index e3ad0fd89..a9851c301 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/artifact.lux @@ -124,7 +124,7 @@ (row\each (value@ #category)) artifacts))) - (exception: .public (invalid_category {tag Nat}) + (exception: .public (invalid_category [tag Nat]) (exception.report ["Tag" (%.nat tag)])) diff --git a/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux b/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux index ddb71ac93..3fcf381d3 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/archive/document.lux @@ -20,7 +20,8 @@ ["[0]" key {"+" [Key]}] [descriptor {"+" [Module]}]]) -(exception: .public (invalid_signature {expected Signature} {actual Signature}) +(exception: .public (invalid_signature [expected Signature + actual Signature]) (exception.report ["Expected" (signature.description expected)] ["Actual" (signature.description actual)])) 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 d6a427d0b..1d7baccbd 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/archive.lux @@ -51,9 +51,9 @@ ["[0]" directive] ["[1]/[0]" program]]]]]]) -(exception: .public (cannot_prepare {archive file.Path} - {module_id archive.ID} - {error Text}) +(exception: .public (cannot_prepare [archive file.Path + module_id archive.ID + error Text]) (exception.report ["Archive" archive] ["Module ID" (%.nat module_id)] 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 177f552e3..af43ef991 100644 --- a/stdlib/source/library/lux/tool/compiler/meta/io/context.lux +++ b/stdlib/source/library/lux/tool/compiler/meta/io/context.lux @@ -31,12 +31,13 @@ [descriptor {"+" [Module]}]] ["/[1]" // {"+" [Input]}]]]) -(exception: .public (cannot_find_module {importer Module} {module Module}) +(exception: .public (cannot_find_module [importer Module + module Module]) (exception.report ["Module" (%.text module)] ["Importer" (%.text importer)])) -(exception: .public (cannot_read_module {module Module}) +(exception: .public (cannot_read_module [module Module]) (exception.report ["Module" (%.text module)])) |