aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/parser
diff options
context:
space:
mode:
authorEduardo Julian2022-08-11 16:50:42 -0400
committerEduardo Julian2022-08-11 16:50:42 -0400
commite5625dd840a8b8adc76987f649da254335d3d93a (patch)
treefb672669383525d90d462edf8c141f98bc953894 /stdlib/source/parser
parent065e8a4d8122d4616b570496915d2c0e2c78cd6b (diff)
Improved exception-definition macro.
Diffstat (limited to 'stdlib/source/parser')
-rw-r--r--stdlib/source/parser/lux/data/binary.lux20
-rw-r--r--stdlib/source/parser/lux/data/collection/tree.lux4
-rw-r--r--stdlib/source/parser/lux/data/format/json.lux14
-rw-r--r--stdlib/source/parser/lux/data/format/xml.lux19
-rw-r--r--stdlib/source/parser/lux/data/text.lux24
-rw-r--r--stdlib/source/parser/lux/meta/compiler/language/lux/analysis.lux16
-rw-r--r--stdlib/source/parser/lux/meta/compiler/language/lux/synthesis.lux27
-rw-r--r--stdlib/source/parser/lux/meta/type.lux14
-rw-r--r--stdlib/source/parser/lux/world/environment.lux5
9 files changed, 76 insertions, 67 deletions
diff --git a/stdlib/source/parser/lux/data/binary.lux b/stdlib/source/parser/lux/data/binary.lux
index 37fc881d3..2a1bf3304 100644
--- a/stdlib/source/parser/lux/data/binary.lux
+++ b/stdlib/source/parser/lux/data/binary.lux
@@ -8,7 +8,7 @@
[control
["//" parser (.use "[1]#[0]" monad)]
["[0]" try (.only Try)]
- ["[0]" exception (.only exception)]]
+ ["[0]" exception (.only Exception)]]
[data
["/" binary
["[1]" \\unsafe (.only Binary)]]
@@ -38,8 +38,8 @@
(.type .public Parser
(//.Parser [Offset Binary]))
-(exception .public (binary_was_not_fully_read [binary_length Nat
- bytes_read Nat])
+(exception.def .public (binary_was_not_fully_read [binary_length bytes_read])
+ (Exception [Nat Nat])
(exception.report
(.list ["Binary length" (%.nat binary_length)]
["Bytes read" (%.nat bytes_read)])))
@@ -89,9 +89,8 @@
(def .public size_32 Size (n.* 2 size_16))
(def .public size_64 Size (n.* 2 size_32))
-(exception .public (range_out_of_bounds [length Nat
- start Nat
- end Nat])
+(exception.def .public (range_out_of_bounds [length start end])
+ (Exception [Nat Nat Nat])
(exception.report
(.list ["Length" (%.nat length)]
["Range start" (%.nat start)]
@@ -126,8 +125,8 @@
(Parser Frac)
(//#each frac.of_bits ..bits_64))
-(exception .public (invalid_tag [range Nat
- byte Nat])
+(exception.def .public (invalid_tag [range byte])
+ (Exception [Nat Nat])
(exception.report
(.list ["Tag range" (%.nat range)]
["Tag value" (%.nat byte)])))
@@ -160,7 +159,8 @@
(Parser Any)
(//#in []))
-(exception .public (not_a_bit [value Nat])
+(exception.def .public (not_a_bit value)
+ (Exception Nat)
(exception.report
(.list ["Expected values" "either 0 or 1"]
["Actual value" (%.nat value)])))
@@ -251,7 +251,7 @@
(|>> (//.and value)
(..or ..any))))
-(exception .public set_elements_are_not_unique)
+(exception.def .public set_elements_are_not_unique)
(def .public (set hash value)
(All (_ a) (-> (Hash a) (Parser a) (Parser (Set a))))
diff --git a/stdlib/source/parser/lux/data/collection/tree.lux b/stdlib/source/parser/lux/data/collection/tree.lux
index 38132cdb4..198460164 100644
--- a/stdlib/source/parser/lux/data/collection/tree.lux
+++ b/stdlib/source/parser/lux/data/collection/tree.lux
@@ -6,7 +6,7 @@
[control
["//" parser]
["[0]" try (.only Try)]
- ["[0]" exception (.only exception)]]]]
+ ["[0]" exception]]]]
[\\library
[/ (.only Tree)
["[0]" zipper (.only Zipper)]]])
@@ -29,7 +29,7 @@
(function (_ zipper)
{try.#Success [zipper (zipper.value zipper)]}))
-(exception .public cannot_move_further)
+(exception.def .public cannot_move_further)
(with_template [<name> <direction>]
[(def .public <name>
diff --git a/stdlib/source/parser/lux/data/format/json.lux b/stdlib/source/parser/lux/data/format/json.lux
index e1c1178e0..aff96d9b7 100644
--- a/stdlib/source/parser/lux/data/format/json.lux
+++ b/stdlib/source/parser/lux/data/format/json.lux
@@ -6,7 +6,7 @@
[control
["//" parser (.use "[1]#[0]" functor)]
["[0]" try (.only Try)]
- ["[0]" exception (.only exception)]]
+ ["[0]" exception (.only Exception)]]
[data
["[0]" bit]
["[0]" text (.use "[1]#[0]" equivalence monoid)]
@@ -25,11 +25,12 @@
(type .public (Parser a)
(//.Parser (List JSON) a))
-(exception .public (unconsumed_input [input (List JSON)])
+(exception.def .public (unconsumed_input input)
+ (Exception (List JSON))
(exception.report
(list ["Input" (exception.listing /.format input)])))
-(exception .public empty_input)
+(exception.def .public empty_input)
(def .public (result parser json)
(All (_ a) (-> (Parser a) JSON (Try a)))
@@ -55,7 +56,8 @@
{.#Item head tail}
{try.#Success [tail head]})))
-(exception .public (unexpected_value [value JSON])
+(exception.def .public (unexpected_value value)
+ (Exception JSON)
(exception.report
(list ["Value" (/.format value)])))
@@ -77,8 +79,8 @@
[string /.String /.#String]
)
-(exception .public [a] (value_mismatch [reference JSON
- sample JSON])
+(exception.def .public (value_mismatch [reference sample])
+ (Exception [JSON JSON])
(exception.report
(list ["Reference" (/.format reference)]
["Sample" (/.format sample)])))
diff --git a/stdlib/source/parser/lux/data/format/xml.lux b/stdlib/source/parser/lux/data/format/xml.lux
index 38d0d33da..ce03568f6 100644
--- a/stdlib/source/parser/lux/data/format/xml.lux
+++ b/stdlib/source/parser/lux/data/format/xml.lux
@@ -6,7 +6,7 @@
[control
["//" parser]
["[0]" try (.only Try) (.use "[1]#[0]" functor)]
- ["[0]" exception (.only exception)]]
+ ["[0]" exception (.only Exception)]]
[data
["[0]" text
["%" \\format (.only format)]]
@@ -21,22 +21,23 @@
(type .public (Parser a)
(//.Parser [Attrs (List XML)] a))
-(exception .public empty_input)
-(exception .public unexpected_input)
+(exception.def .public empty_input)
+(exception.def .public unexpected_input)
-(exception .public (wrong_tag [expected Tag
- actual Tag])
+(exception.def .public (wrong_tag [expected actual])
+ (Exception [Tag Tag])
(exception.report
(list ["Expected" (%.text (/.tag expected))]
["Actual" (%.text (/.tag actual))])))
-(exception .public (unknown_attribute [expected Attribute
- available (List Attribute)])
+(exception.def .public (unknown_attribute [expected available])
+ (Exception [Attribute (List Attribute)])
(exception.report
(list ["Expected" (%.text (/.attribute expected))]
["Available" (exception.listing (|>> /.attribute %.text) available)])))
-(exception .public (unconsumed_inputs [inputs (List XML)])
+(exception.def .public (unconsumed_inputs inputs)
+ (Exception (List XML))
(exception.report
(list ["Inputs" (exception.listing (at /.codec encoded) inputs)])))
@@ -124,7 +125,7 @@
{.#Item head tail}
{try.#Success [[attrs tail] head]})))
-(exception .public nowhere)
+(exception.def .public nowhere)
(def .public (somewhere parser)
(All (_ a) (-> (Parser a) (Parser a)))
diff --git a/stdlib/source/parser/lux/data/text.lux b/stdlib/source/parser/lux/data/text.lux
index 28320b351..50bb41cb3 100644
--- a/stdlib/source/parser/lux/data/text.lux
+++ b/stdlib/source/parser/lux/data/text.lux
@@ -7,7 +7,7 @@
["//" parser]
["[0]" maybe]
["[0]" try (.only Try)]
- ["[0]" exception (.only exception)]]
+ ["[0]" exception (.only Exception)]]
[data
["/" text (.only Char) (.use "[1]#[0]" monoid)]
["[0]" product]
@@ -29,8 +29,8 @@
Offset
0)
-(exception .public cannot_parse)
-(exception .public cannot_slice)
+(exception.def .public cannot_parse)
+(exception.def .public cannot_slice)
(type .public Parser
(//.Parser [Offset Text]))
@@ -56,15 +56,15 @@
(-> Offset Text Text)
(|> tape (/.clip_since offset) maybe.trusted))
-(exception .public (unconsumed_input [offset Offset
- tape Text])
+(exception.def .public (unconsumed_input [offset tape])
+ (Exception [Offset Text])
(exception.report
(list ["Offset" (n#encoded offset)]
["Input size" (n#encoded (/.size tape))]
["Remaining input" (..left_over offset tape)])))
-(exception .public (expected_to_fail [offset Offset
- tape Text])
+(exception.def .public (expected_to_fail [offset tape])
+ (Exception [Offset Text])
(exception.report
(list ["Offset" (n#encoded offset)]
["Input" (..left_over offset tape)])))
@@ -134,7 +134,8 @@
[not! Slice ..any!]
)
-(exception .public (cannot_match [reference Text])
+(exception.def .public (cannot_match reference)
+ (Exception Text)
(exception.report
(list ["Reference" (/.format reference)])))
@@ -230,8 +231,8 @@
(..range! (char "A") (char "F"))))
(with_template [<name>]
- [(exception .public (<name> [options Text
- character Char])
+ [(exception.def .public (<name> [options character])
+ (Exception [Text Char])
(exception.report
(list ["Options" (/.format options)]
["Character" (/.format (/.of_char character))])))]
@@ -278,7 +279,8 @@
[none_of! .not ..character_should_not_be]
)
-(exception .public (character_does_not_satisfy_predicate [character Char])
+(exception.def .public (character_does_not_satisfy_predicate character)
+ (Exception Char)
(exception.report
(list ["Character" (/.format (/.of_char character))])))
diff --git a/stdlib/source/parser/lux/meta/compiler/language/lux/analysis.lux b/stdlib/source/parser/lux/meta/compiler/language/lux/analysis.lux
index 0d98f3bd4..968085cc4 100644
--- a/stdlib/source/parser/lux/meta/compiler/language/lux/analysis.lux
+++ b/stdlib/source/parser/lux/meta/compiler/language/lux/analysis.lux
@@ -6,7 +6,7 @@
[control
["//" parser]
["[0]" try (.only Try)]
- ["[0]" exception (.only exception)]]
+ ["[0]" exception (.only Exception)]]
[data
["[0]" bit]
["[0]" text (.only)
@@ -37,13 +37,15 @@
(list#each /.format)
(text.interposed " "))))
-(exception .public (cannot_parse [input (List Analysis)])
- (exception.report
- (list ["Input" (exception.listing /.format input)])))
+(with_template [<name>]
+ [(exception.def .public (<name> input)
+ (Exception (List Analysis))
+ (exception.report
+ (list ["Input" (exception.listing /.format input)])))]
-(exception .public (unconsumed_input [input (List Analysis)])
- (exception.report
- (list ["Input" (exception.listing /.format input)])))
+ [cannot_parse]
+ [unconsumed_input]
+ )
(type .public Parser
(//.Parser (List Analysis)))
diff --git a/stdlib/source/parser/lux/meta/compiler/language/lux/synthesis.lux b/stdlib/source/parser/lux/meta/compiler/language/lux/synthesis.lux
index fda40e0cd..2cb179d28 100644
--- a/stdlib/source/parser/lux/meta/compiler/language/lux/synthesis.lux
+++ b/stdlib/source/parser/lux/meta/compiler/language/lux/synthesis.lux
@@ -6,7 +6,7 @@
[control
["//" parser]
["[0]" try (.only Try)]
- ["[0]" exception (.only exception)]]
+ ["[0]" exception (.only Exception)]]
[data
["[0]" bit]
["[0]" text (.only)
@@ -30,25 +30,24 @@
[\\library
["[0]" / (.only Synthesis Abstraction)]])
-(exception .public (cannot_parse [input (List Synthesis)])
- (exception.report
- (list ["Input" (exception.listing /.%synthesis input)])))
-
-(exception .public (unconsumed_input [input (List Synthesis)])
- (exception.report
- (list ["Input" (exception.listing /.%synthesis input)])))
+(with_template [<name>]
+ [(exception.def .public (<name> input)
+ (Exception (List Synthesis))
+ (exception.report
+ (list ["Input" (exception.listing /.%synthesis input)])))]
-(exception .public (expected_empty_input [input (List Synthesis)])
- (exception.report
- (list ["Input" (exception.listing /.%synthesis input)])))
+ [cannot_parse]
+ [unconsumed_input]
+ [expected_empty_input]
+ )
-(exception .public (wrong_arity [expected Arity
- actual Arity])
+(exception.def .public (wrong_arity [expected actual])
+ (Exception [Arity Arity])
(exception.report
(list ["Expected" (%.nat expected)]
["Actual" (%.nat actual)])))
-(exception .public empty_input)
+(exception.def .public empty_input)
(type .public Parser
(//.Parser (List Synthesis)))
diff --git a/stdlib/source/parser/lux/meta/type.lux b/stdlib/source/parser/lux/meta/type.lux
index f93efcd6d..1dec4fbb1 100644
--- a/stdlib/source/parser/lux/meta/type.lux
+++ b/stdlib/source/parser/lux/meta/type.lux
@@ -6,7 +6,7 @@
[control
["//" parser]
["[0]" try (.only Try)]
- ["[0]" exception (.only exception)]
+ ["[0]" exception (.only Exception)]
["[0]" function]]
[data
["[0]" text (.use "[1]#[0]" monoid)
@@ -30,7 +30,8 @@
[{.#Primitive "" {.#End}}]))
(with_template [<name>]
- [(exception .public (<name> [type Type])
+ [(exception.def .public (<name> type)
+ (Exception Type)
(exception.report
(list ["Type" (%.type type)])))]
@@ -47,8 +48,8 @@
)
(with_template [<name>]
- [(exception .public (<name> [expected Type
- actual Type])
+ [(exception.def .public (<name> [expected actual])
+ (Exception [Type Type])
(exception.report
(list ["Expected" (%.type expected)]
["Actual" (%.type actual)])))]
@@ -57,9 +58,10 @@
[wrong_parameter]
)
-(exception .public empty_input)
+(exception.def .public empty_input)
-(exception .public (unconsumed_input [remaining (List Type)])
+(exception.def .public (unconsumed_input remaining)
+ (Exception (List Type))
(exception.report
(list ["Types" (|> remaining
(list#each (|>> %.type (format text.new_line "* ")))
diff --git a/stdlib/source/parser/lux/world/environment.lux b/stdlib/source/parser/lux/world/environment.lux
index 10230d5a1..3b8a3049b 100644
--- a/stdlib/source/parser/lux/world/environment.lux
+++ b/stdlib/source/parser/lux/world/environment.lux
@@ -4,7 +4,7 @@
[control
["//" parser]
["[0]" try (.only Try)]
- ["[0]" exception (.only exception)]]
+ ["[0]" exception (.only Exception)]]
[data
["[0]" product]
["[0]" text (.only)
@@ -18,7 +18,8 @@
(type .public Environment
(Dictionary Property Text))
-(exception .public (unknown_property [property Property])
+(exception.def .public (unknown_property property)
+ (Exception Property)
(exception.report
(list ["Property" (%.text property)])))