aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/control/parser
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/control/parser.lux18
-rw-r--r--stdlib/source/lux/control/parser/analysis.lux24
-rw-r--r--stdlib/source/lux/control/parser/binary.lux24
-rw-r--r--stdlib/source/lux/control/parser/cli.lux40
-rw-r--r--stdlib/source/lux/control/parser/code.lux34
-rw-r--r--stdlib/source/lux/control/parser/json.lux42
-rw-r--r--stdlib/source/lux/control/parser/synthesis.lux36
-rw-r--r--stdlib/source/lux/control/parser/text.lux128
-rw-r--r--stdlib/source/lux/control/parser/type.lux178
-rw-r--r--stdlib/source/lux/control/parser/xml.lux38
10 files changed, 281 insertions, 281 deletions
diff --git a/stdlib/source/lux/control/parser.lux b/stdlib/source/lux/control/parser.lux
index 1cb4e2298..8f896cf39 100644
--- a/stdlib/source/lux/control/parser.lux
+++ b/stdlib/source/lux/control/parser.lux
@@ -163,7 +163,7 @@
(wrap (#.Cons x xs)))
(\ ..monad wrap (list))))
-(def: #export (at-least n p)
+(def: #export (at_least n p)
{#.doc "Parse at least N times."}
(All [s a] (-> Nat (Parser s a) (Parser s (List a))))
(do ..monad
@@ -171,7 +171,7 @@
extra (some p)]
(wrap (list\compose min extra))))
-(def: #export (at-most n p)
+(def: #export (at_most n p)
{#.doc "Parse at most N times."}
(All [s a] (-> Nat (Parser s a) (Parser s (List a))))
(if (n.> 0 n)
@@ -182,7 +182,7 @@
(#try.Success [input' x])
(run (do ..monad
- [xs (at-most (dec n) p)]
+ [xs (at_most (dec n) p)]
(wrap (#.Cons x xs)))
input')
))
@@ -192,11 +192,11 @@
{#.doc "Parse between N and M times."}
(All [s a] (-> Nat Nat (Parser s a) (Parser s (List a))))
(do ..monad
- [min-xs (exactly from p)
- max-xs (at-most (n.- from to) p)]
- (wrap (\ list.monad join (list min-xs max-xs)))))
+ [min_xs (exactly from p)
+ max_xs (at_most (n.- from to) p)]
+ (wrap (\ list.monad join (list min_xs max_xs)))))
-(def: #export (sep-by sep p)
+(def: #export (sep_by sep p)
{#.doc "Parsers instances of 'p' that are separated by instances of 'sep'."}
(All [s a b] (-> (Parser s b) (Parser s a) (Parser s (List a))))
(do {! ..monad}
@@ -315,8 +315,8 @@
(#try.Failure error)
(#try.Failure error)
- (#try.Success [input' to-decode])
- (case (\ codec decode to-decode)
+ (#try.Success [input' to_decode])
+ (case (\ codec decode to_decode)
(#try.Failure error)
(#try.Failure error)
diff --git a/stdlib/source/lux/control/parser/analysis.lux b/stdlib/source/lux/control/parser/analysis.lux
index d62dca0e8..6a7a1c407 100644
--- a/stdlib/source/lux/control/parser/analysis.lux
+++ b/stdlib/source/lux/control/parser/analysis.lux
@@ -26,19 +26,19 @@
["/" analysis (#+ Variant Tuple Environment Analysis)]]]]]]
["." //])
-(def: (remaining-inputs asts)
+(def: (remaining_inputs asts)
(-> (List Analysis) Text)
- (format text.new-line "Remaining input: "
+ (format text.new_line "Remaining input: "
(|> asts
(list\map /.%analysis)
(list.interpose " ")
- (text.join-with ""))))
+ (text.join_with ""))))
-(exception: #export (cannot-parse {input (List Analysis)})
+(exception: #export (cannot_parse {input (List Analysis)})
(exception.report
["Input" (exception.enumerate /.%analysis input)]))
-(exception: #export (unconsumed-input {input (List Analysis)})
+(exception: #export (unconsumed_input {input (List Analysis)})
(exception.report
["Input" (exception.enumerate /.%analysis input)]))
@@ -55,14 +55,14 @@
(#try.Success value)
(#try.Success [unconsumed _])
- (exception.throw ..unconsumed-input unconsumed)))
+ (exception.throw ..unconsumed_input unconsumed)))
(def: #export any
(Parser Analysis)
(function (_ input)
(case input
#.Nil
- (exception.throw ..cannot-parse input)
+ (exception.throw ..cannot_parse input)
(#.Cons [head tail])
(#try.Success [tail head]))))
@@ -74,7 +74,7 @@
(case tokens
#.Nil (#try.Success [tokens []])
_ (#try.Failure (format "Expected list of tokens to be empty!"
- (remaining-inputs tokens))))))
+ (remaining_inputs tokens))))))
(def: #export end?
{#.doc "Checks whether there are no more inputs."}
@@ -93,7 +93,7 @@
(#try.Success [input' x])
_
- (exception.throw ..cannot-parse input))))
+ (exception.throw ..cannot_parse input))))
(def: #export (<assertion> expected)
(-> <type> (Parser Any))
@@ -102,10 +102,10 @@
(^ (list& (<tag> actual) input'))
(if (\ <eq> = expected actual)
(#try.Success [input' []])
- (exception.throw ..cannot-parse input))
+ (exception.throw ..cannot_parse input))
_
- (exception.throw ..cannot-parse input))))]
+ (exception.throw ..cannot_parse input))))]
[bit bit! /.bit Bit bit.equivalence]
[nat nat! /.nat Nat nat.equivalence]
@@ -128,4 +128,4 @@
(#try.Success [tail output]))
_
- (exception.throw ..cannot-parse input))))
+ (exception.throw ..cannot_parse input))))
diff --git a/stdlib/source/lux/control/parser/binary.lux b/stdlib/source/lux/control/parser/binary.lux
index 03bcc9eba..32750d535 100644
--- a/stdlib/source/lux/control/parser/binary.lux
+++ b/stdlib/source/lux/control/parser/binary.lux
@@ -28,10 +28,10 @@
(type: #export Parser
(//.Parser [Offset Binary]))
-(exception: #export (binary-was-not-fully-read {binary-length Nat} {bytes-read Nat})
+(exception: #export (binary_was_not_fully_read {binary_length Nat} {bytes_read Nat})
(exception.report
- ["Binary length" (%.nat binary-length)]
- ["Bytes read" (%.nat bytes-read)]))
+ ["Binary length" (%.nat binary_length)]
+ ["Bytes read" (%.nat bytes_read)]))
(def: #export (run parser input)
(All [a] (-> (Parser a) Binary (Try a)))
@@ -43,7 +43,7 @@
(let [length (/.size input)]
(if (n.= end length)
(#try.Success output)
- (exception.throw ..binary-was-not-fully-read [length end])))))
+ (exception.throw ..binary_was_not_fully_read [length end])))))
(def: #export end?
(Parser Bit)
@@ -94,9 +94,9 @@
(def: #export frac
(Parser Frac)
- (//\map frac.from-bits ..bits/64))
+ (//\map frac.from_bits ..bits/64))
-(exception: #export (invalid-tag {range Nat} {byte Nat})
+(exception: #export (invalid_tag {range Nat} {byte Nat})
(exception.report
["Tag range" (%.nat range)]
["Tag value" (%.nat byte)]))
@@ -109,7 +109,7 @@
(^template [<number> <tag> <parser>]
[<number> (\ ! map (|>> <tag>) <parser>)])
((~~ (template.splice <case>+)))
- _ (//.lift (exception.throw ..invalid-tag [(~~ (template.count <case>+)) flag]))))))
+ _ (//.lift (exception.throw ..invalid_tag [(~~ (template.count <case>+)) flag]))))))
(def: #export (or left right)
(All [l r] (-> (Parser l) (Parser r) (Parser (| l r))))
@@ -126,7 +126,7 @@
(Parser Any)
(//\wrap []))
-(exception: #export (not-a-bit {value Nat})
+(exception: #export (not_a_bit {value Nat})
(exception.report
["Expected values" "either 0 or 1"]
["Actual value" (%.nat value)]))
@@ -139,7 +139,7 @@
(case value
0 (wrap #0)
1 (wrap #1)
- _ (//.lift (exception.throw ..not-a-bit [value])))))
+ _ (//.lift (exception.throw ..not_a_bit [value])))))
(def: #export (segment size)
(-> Nat (Parser Binary))
@@ -214,14 +214,14 @@
(|>> (//.and value)
(..or ..any))))
-(exception: #export set-elements-are-not-unique)
+(exception: #export set_elements_are_not_unique)
(def: #export (set hash value)
(All [a] (-> (Hash a) (Parser a) (Parser (Set a))))
(do //.monad
[raw (..list value)
- #let [output (set.from-list hash raw)]
- _ (//.assert (exception.construct ..set-elements-are-not-unique [])
+ #let [output (set.from_list hash raw)]
+ _ (//.assert (exception.construct ..set_elements_are_not_unique [])
(n.= (list.size raw)
(set.size output)))]
(wrap output)))
diff --git a/stdlib/source/lux/control/parser/cli.lux b/stdlib/source/lux/control/parser/cli.lux
index de654eb24..7df6e448e 100644
--- a/stdlib/source/lux/control/parser/cli.lux
+++ b/stdlib/source/lux/control/parser/cli.lux
@@ -10,7 +10,7 @@
["." list ("#\." monoid monad)]]
["." text ("#\." equivalence)
["%" format (#+ format)]]]
- [meta (#+ with-gensyms)]
+ [meta (#+ with_gensyms)]
[macro
["." code]
[syntax (#+ syntax:)]]]
@@ -34,7 +34,7 @@
(#try.Success output)
_
- (#try.Failure (format "Remaining CLI inputs: " (text.join-with " " remaining))))
+ (#try.Failure (format "Remaining CLI inputs: " (text.join_with " " remaining))))
(#try.Failure try)
(#try.Failure try)))
@@ -83,10 +83,10 @@
#.Nil
(#try.Failure try)
- (#.Cons to-omit immediate')
+ (#.Cons to_omit immediate')
(do try.monad
[[remaining output] (recur immediate')]
- (wrap [(#.Cons to-omit remaining)
+ (wrap [(#.Cons to_omit remaining)
output])))))))
(def: #export end
@@ -95,7 +95,7 @@
(function (_ inputs)
(case inputs
#.Nil (#try.Success [inputs []])
- _ (#try.Failure (format "Unknown parameters: " (text.join-with " " inputs))))))
+ _ (#try.Failure (format "Unknown parameters: " (text.join_with " " inputs))))))
(def: #export (named name value)
(All [a] (-> Text (Parser a) (Parser a)))
@@ -109,27 +109,27 @@
(//.after (//.either (..this short) (..this long)))
..somewhere))
-(type: Program-Args
+(type: Program_Args
(#Raw Text)
(#Parsed (List [Code Code])))
-(def: program-args^
- (s.Parser Program-Args)
- (//.or s.local-identifier
+(def: program_args^
+ (s.Parser Program_Args)
+ (//.or s.local_identifier
(s.tuple (//.some (//.either (do //.monad
- [name s.local-identifier]
+ [name s.local_identifier]
(wrap [(code.identifier ["" name]) (` any)]))
(s.record (//.and s.any s.any)))))))
(syntax: #export (program:
- {args program-args^}
+ {args program_args^}
body)
{#.doc (doc "Defines the entry-point to a program (similar to the 'main' function/method in other programming languages)."
"Can take a list of all the input parameters to the program, or can destructure them using CLI-option combinators from the lux/cli module."
- (program: all-args
+ (program: all_args
(do io.monad
- [foo init-program
- bar (do-something all-args)]
+ [foo init_program
+ bar (do_something all_args)]
(wrap [])))
(program: [name]
@@ -137,10 +137,10 @@
(program: [{config config^}]
(do io.monad
- [data (init-program config)]
- (do-something data))))}
- (with-gensyms [g!program g!args g!_ g!output g!message]
- (let [initialization+event-loop
+ [data (init_program config)]
+ (do_something data))))}
+ (with_gensyms [g!program g!args g!_ g!output g!message]
+ (let [initialization+event_loop
(` ((~! do) (~! io.monad)
[(~ g!output) (~ body)
(~+ (for {@.old
@@ -158,7 +158,7 @@
(#Raw args)
(wrap (list (` ("lux def program"
(.function ((~ g!program) (~ (code.identifier ["" args])))
- (~ initialization+event-loop))))))
+ (~ initialization+event_loop))))))
(#Parsed args)
(wrap (list (` ("lux def program"
@@ -169,7 +169,7 @@
(list\map (function (_ [binding parser])
(list binding parser)))
list\join))]
- ((~' wrap) (~ initialization+event-loop))))
+ ((~' wrap) (~ initialization+event_loop))))
(~ g!args))
(#.Right [(~ g!_) (~ g!output)])
(~ g!output)
diff --git a/stdlib/source/lux/control/parser/code.lux b/stdlib/source/lux/control/parser/code.lux
index 9dc99e49a..82f5fbca8 100644
--- a/stdlib/source/lux/control/parser/code.lux
+++ b/stdlib/source/lux/control/parser/code.lux
@@ -19,20 +19,20 @@
["." code ("#\." equivalence)]]]
["." //])
-(def: (join-pairs pairs)
+(def: (join_pairs pairs)
(All [a] (-> (List [a a]) (List a)))
(case pairs
#.Nil #.Nil
- (#.Cons [[x y] pairs']) (list& x y (join-pairs pairs'))))
+ (#.Cons [[x y] pairs']) (list& x y (join_pairs pairs'))))
(type: #export Parser
{#.doc "A Lux syntax parser."}
(//.Parser (List Code)))
-(def: (remaining-inputs asts)
+(def: (remaining_inputs asts)
(-> (List Code) Text)
- ($_ text\compose text.new-line "Remaining input: "
- (|> asts (list\map code.format) (list.interpose " ") (text.join-with ""))))
+ ($_ text\compose text.new_line "Remaining input: "
+ (|> asts (list\map code.format) (list.interpose " ") (text.join_with ""))))
(def: #export any
{#.doc "Just returns the next input without applying any logic."}
@@ -46,7 +46,7 @@
(#try.Success [tokens' t]))))
(template [<query> <check> <type> <tag> <eq> <desc>]
- [(with-expansions [<failure> (as-is (#try.Failure ($_ text\compose "Cannot parse " <desc> (remaining-inputs tokens))))]
+ [(with_expansions [<failure> (as_is (#try.Failure ($_ text\compose "Cannot parse " <desc> (remaining_inputs tokens))))]
(def: #export <query>
{#.doc (code.text ($_ text\compose "Parses the next " <desc> " input."))}
(Parser <type>)
@@ -89,13 +89,13 @@
(if (code\= ast token)
(#try.Success [tokens' []])
(#try.Failure ($_ text\compose "Expected a " (code.format ast) " but instead got " (code.format token)
- (remaining-inputs tokens))))
+ (remaining_inputs tokens))))
_
(#try.Failure "There are no tokens to parse!"))))
(template [<query> <check> <tag> <eq> <desc>]
- [(with-expansions [<failure> (as-is (#try.Failure ($_ text\compose "Cannot parse " <desc> (remaining-inputs tokens))))]
+ [(with_expansions [<failure> (as_is (#try.Failure ($_ text\compose "Cannot parse " <desc> (remaining_inputs tokens))))]
(def: #export <query>
{#.doc (code.text ($_ text\compose "Parse a local " <desc> " (a " <desc> " that has no module prefix)."))}
(Parser Text)
@@ -119,8 +119,8 @@
_
<failure>))))]
- [local-identifier local-identifier! #.Identifier text.equivalence "local identifier"]
- [ local-tag local-tag! #.Tag text.equivalence "local tag"]
+ [local_identifier local_identifier! #.Identifier text.equivalence "local identifier"]
+ [ local_tag local_tag! #.Tag text.equivalence "local tag"]
)
(template [<name> <tag> <desc>]
@@ -133,10 +133,10 @@
(#.Cons [[_ (<tag> members)] tokens'])
(case (p members)
(#try.Success [#.Nil x]) (#try.Success [tokens' x])
- _ (#try.Failure ($_ text\compose "Parser was expected to fully consume " <desc> (remaining-inputs tokens))))
+ _ (#try.Failure ($_ text\compose "Parser was expected to fully consume " <desc> (remaining_inputs tokens))))
_
- (#try.Failure ($_ text\compose "Cannot parse " <desc> (remaining-inputs tokens))))))]
+ (#try.Failure ($_ text\compose "Cannot parse " <desc> (remaining_inputs tokens))))))]
[ form #.Form "form"]
[tuple #.Tuple "tuple"]
@@ -149,12 +149,12 @@
(function (_ tokens)
(case tokens
(#.Cons [[_ (#.Record pairs)] tokens'])
- (case (p (join-pairs pairs))
+ (case (p (join_pairs pairs))
(#try.Success [#.Nil x]) (#try.Success [tokens' x])
- _ (#try.Failure ($_ text\compose "Parser was expected to fully consume record" (remaining-inputs tokens))))
+ _ (#try.Failure ($_ text\compose "Parser was expected to fully consume record" (remaining_inputs tokens))))
_
- (#try.Failure ($_ text\compose "Cannot parse record" (remaining-inputs tokens))))))
+ (#try.Failure ($_ text\compose "Cannot parse record" (remaining_inputs tokens))))))
(def: #export end!
{#.doc "Ensures there are no more inputs."}
@@ -162,7 +162,7 @@
(function (_ tokens)
(case tokens
#.Nil (#try.Success [tokens []])
- _ (#try.Failure ($_ text\compose "Expected list of tokens to be empty!" (remaining-inputs tokens))))))
+ _ (#try.Failure ($_ text\compose "Expected list of tokens to be empty!" (remaining_inputs tokens))))))
(def: #export end?
{#.doc "Checks whether there are no more inputs."}
@@ -186,7 +186,7 @@
_
(#try.Failure (text\compose "Unconsumed inputs: "
(|> (list\map code.format unconsumed)
- (text.join-with ", ")))))))
+ (text.join_with ", ")))))))
(def: #export (local inputs syntax)
{#.doc "Run a syntax parser with the given list of inputs, instead of the real ones."}
diff --git a/stdlib/source/lux/control/parser/json.lux b/stdlib/source/lux/control/parser/json.lux
index a7cf8fa9f..9035d41fe 100644
--- a/stdlib/source/lux/control/parser/json.lux
+++ b/stdlib/source/lux/control/parser/json.lux
@@ -24,11 +24,11 @@
{#.doc "JSON parser."}
(//.Parser (List JSON) a))
-(exception: #export (unconsumed-input {input (List JSON)})
+(exception: #export (unconsumed_input {input (List JSON)})
(exception.report
["Input" (exception.enumerate /.format input)]))
-(exception: #export empty-input)
+(exception: #export empty_input)
(def: #export (run parser json)
(All [a] (-> (Parser a) JSON (Try a)))
@@ -39,7 +39,7 @@
(#try.Success output)
_
- (exception.throw ..unconsumed-input remainder))
+ (exception.throw ..unconsumed_input remainder))
(#try.Failure error)
(#try.Failure error)))
@@ -50,12 +50,12 @@
(<| (function (_ inputs))
(case inputs
#.Nil
- (exception.throw ..empty-input [])
+ (exception.throw ..empty_input [])
(#.Cons head tail)
(#try.Success [tail head]))))
-(exception: #export (unexpected-value {value JSON})
+(exception: #export (unexpected_value {value JSON})
(exception.report
["Value" (/.format value)]))
@@ -70,7 +70,7 @@
(wrap value)
_
- (//.fail (exception.construct ..unexpected-value [head])))))]
+ (//.fail (exception.construct ..unexpected_value [head])))))]
[null /.Null #/.Null "null"]
[boolean /.Boolean #/.Boolean "boolean"]
@@ -78,7 +78,7 @@
[string /.String #/.String "string"]
)
-(exception: #export [a] (value-mismatch {reference JSON} {sample JSON})
+(exception: #export [a] (value_mismatch {reference JSON} {sample JSON})
(exception.report
["Reference" (/.format reference)]
["Sample" (/.format sample)]))
@@ -94,7 +94,7 @@
(wrap (\ <equivalence> = test value))
_
- (//.fail (exception.construct ..unexpected-value [head])))))
+ (//.fail (exception.construct ..unexpected_value [head])))))
(def: #export (<check> test)
{#.doc (code.text ($_ text\compose "Ensures a JSON value is a " <desc> "."))}
@@ -105,10 +105,10 @@
(<tag> value)
(if (\ <equivalence> = test value)
(wrap [])
- (//.fail (exception.construct ..value-mismatch [(<tag> test) (<tag> value)])))
+ (//.fail (exception.construct ..value_mismatch [(<tag> test) (<tag> value)])))
_
- (//.fail (exception.construct ..unexpected-value [head])))))]
+ (//.fail (exception.construct ..unexpected_value [head])))))]
[boolean? boolean! /.Boolean bit.equivalence #/.Boolean "boolean"]
[number? number! /.Number frac.equivalence #/.Number "number"]
@@ -127,7 +127,7 @@
[head ..any]
(case head
(#/.Array values)
- (case (//.run parser (row.to-list values))
+ (case (//.run parser (row.to_list values))
(#try.Failure error)
(//.fail error)
@@ -137,10 +137,10 @@
(wrap output)
_
- (//.fail (exception.construct ..unconsumed-input remainder))))
+ (//.fail (exception.construct ..unconsumed_input remainder))))
_
- (//.fail (exception.construct ..unexpected-value [head])))))
+ (//.fail (exception.construct ..unexpected_value [head])))))
(def: #export (object parser)
{#.doc "Parses a JSON object. Use this with the 'field' combinator."}
@@ -164,24 +164,24 @@
(wrap output)
_
- (//.fail (exception.construct ..unconsumed-input remainder))))
+ (//.fail (exception.construct ..unconsumed_input remainder))))
_
- (//.fail (exception.construct ..unexpected-value [head])))))
+ (//.fail (exception.construct ..unexpected_value [head])))))
-(def: #export (field field-name parser)
+(def: #export (field field_name parser)
{#.doc "Parses a field inside a JSON object. Use this inside the 'object' combinator."}
(All [a] (-> Text (Parser a) (Parser a)))
(function (recur inputs)
(case inputs
(^ (list& (#/.String key) value inputs'))
- (if (text\= key field-name)
+ (if (text\= key field_name)
(case (//.run parser (list value))
(#try.Success [#.Nil output])
(#try.Success [inputs' output])
(#try.Success [inputs'' _])
- (exception.throw ..unconsumed-input inputs'')
+ (exception.throw ..unconsumed_input inputs'')
(#try.Failure error)
(#try.Failure error))
@@ -191,10 +191,10 @@
output])))
#.Nil
- (exception.throw ..empty-input [])
+ (exception.throw ..empty_input [])
_
- (exception.throw ..unconsumed-input inputs))))
+ (exception.throw ..unconsumed_input inputs))))
(def: #export dictionary
{#.doc "Parses a dictionary-like JSON object."}
@@ -202,4 +202,4 @@
(|>> (//.and ..string)
//.some
..object
- (//\map (dictionary.from-list text.hash))))
+ (//\map (dictionary.from_list text.hash))))
diff --git a/stdlib/source/lux/control/parser/synthesis.lux b/stdlib/source/lux/control/parser/synthesis.lux
index e5b0bda2a..ad376d059 100644
--- a/stdlib/source/lux/control/parser/synthesis.lux
+++ b/stdlib/source/lux/control/parser/synthesis.lux
@@ -30,24 +30,24 @@
Type
(type (List Synthesis)))
-(exception: #export (cannot-parse {input ..Input})
+(exception: #export (cannot_parse {input ..Input})
(exception.report
["Input" (exception.enumerate /.%synthesis input)]))
-(exception: #export (unconsumed-input {input ..Input})
+(exception: #export (unconsumed_input {input ..Input})
(exception.report
["Input" (exception.enumerate /.%synthesis input)]))
-(exception: #export (expected-empty-input {input ..Input})
+(exception: #export (expected_empty_input {input ..Input})
(exception.report
["Input" (exception.enumerate /.%synthesis input)]))
-(exception: #export (wrong-arity {expected Arity} {actual Arity})
+(exception: #export (wrong_arity {expected Arity} {actual Arity})
(exception.report
["Expected" (%.nat expected)]
["Actual" (%.nat actual)]))
-(exception: #export empty-input)
+(exception: #export empty_input)
(type: #export Parser
(//.Parser ..Input))
@@ -62,14 +62,14 @@
(#try.Success value)
(#try.Success [unconsumed _])
- (exception.throw ..unconsumed-input unconsumed)))
+ (exception.throw ..unconsumed_input unconsumed)))
(def: #export any
(Parser Synthesis)
(.function (_ input)
(case input
#.Nil
- (exception.throw ..empty-input [])
+ (exception.throw ..empty_input [])
(#.Cons [head tail])
(#try.Success [tail head]))))
@@ -80,7 +80,7 @@
(.function (_ tokens)
(case tokens
#.Nil (#try.Success [tokens []])
- _ (exception.throw ..expected-empty-input [tokens]))))
+ _ (exception.throw ..expected_empty_input [tokens]))))
(def: #export end?
{#.doc "Checks whether there are no more inputs."}
@@ -99,7 +99,7 @@
(#try.Success [input' x])
_
- (exception.throw ..cannot-parse input))))
+ (exception.throw ..cannot_parse input))))
(def: #export (<assertion> expected)
(-> <type> (Parser Any))
@@ -108,10 +108,10 @@
(^ (list& (<tag> actual) input'))
(if (\ <eq> = expected actual)
(#try.Success [input' []])
- (exception.throw ..cannot-parse input))
+ (exception.throw ..cannot_parse input))
_
- (exception.throw ..cannot-parse input))))]
+ (exception.throw ..cannot_parse input))))]
[bit bit! /.bit Bit bit.equivalence]
[i64 i64! /.i64 (I64 Any) i64.equivalence]
@@ -132,7 +132,7 @@
(#try.Success [tail output]))
_
- (exception.throw ..cannot-parse input))))
+ (exception.throw ..cannot_parse input))))
(def: #export (function expected parser)
(All [a] (-> Arity (Parser a) (Parser [(Environment Synthesis) a])))
@@ -143,20 +143,20 @@
(do try.monad
[output (..run parser (list body))]
(#try.Success [tail [environment output]]))
- (exception.throw ..wrong-arity [expected actual]))
+ (exception.throw ..wrong_arity [expected actual]))
_
- (exception.throw ..cannot-parse input))))
+ (exception.throw ..cannot_parse input))))
-(def: #export (loop init-parsers iteration-parser)
+(def: #export (loop init_parsers iteration_parser)
(All [a b] (-> (Parser a) (Parser b) (Parser [Register a b])))
(.function (_ input)
(case input
(^ (list& (/.loop/scope [start inits iteration]) tail))
(do try.monad
- [inits (..run init-parsers inits)
- iteration (..run iteration-parser (list iteration))]
+ [inits (..run init_parsers inits)
+ iteration (..run iteration_parser (list iteration))]
(#try.Success [tail [start inits iteration]]))
_
- (exception.throw ..cannot-parse input))))
+ (exception.throw ..cannot_parse input))))
diff --git a/stdlib/source/lux/control/parser/text.lux b/stdlib/source/lux/control/parser/text.lux
index ebcf3c53a..919de78c4 100644
--- a/stdlib/source/lux/control/parser/text.lux
+++ b/stdlib/source/lux/control/parser/text.lux
@@ -19,7 +19,7 @@
(type: #export Offset Nat)
-(def: start-offset Offset 0)
+(def: start_offset Offset 0)
(type: #export Parser
(//.Parser [Offset Text]))
@@ -32,37 +32,37 @@
(-> Offset Text Text)
(|> tape (/.split offset) maybe.assume product.right))
-(exception: #export (unconsumed-input {offset Offset} {tape Text})
+(exception: #export (unconsumed_input {offset Offset} {tape Text})
(exception.report
["Offset" (n\encode offset)]
["Input size" (n\encode (/.size tape))]
["Remaining input" (remaining offset tape)]))
-(exception: #export (expected-to-fail {offset Offset} {tape Text})
+(exception: #export (expected_to_fail {offset Offset} {tape Text})
(exception.report
["Offset" (n\encode offset)]
["Input" (remaining offset tape)]))
-(exception: #export cannot-parse)
-(exception: #export cannot-slice)
+(exception: #export cannot_parse)
+(exception: #export cannot_slice)
(def: #export (run parser input)
(All [a] (-> (Parser a) Text (Try a)))
- (case (parser [start-offset input])
+ (case (parser [start_offset input])
(#try.Failure msg)
(#try.Failure msg)
- (#try.Success [[end-offset _] output])
- (if (n.= end-offset (/.size input))
+ (#try.Success [[end_offset _] output])
+ (if (n.= end_offset (/.size input))
(#try.Success output)
- (exception.throw ..unconsumed-input [end-offset input]))))
+ (exception.throw ..unconsumed_input [end_offset input]))))
(def: #export offset
(Parser Offset)
(function (_ (^@ input [offset tape]))
(#try.Success [input offset])))
-(def: (with-slices parser)
+(def: (with_slices parser)
(-> (Parser (List Slice)) (Parser Slice))
(do //.monad
[offset ..offset
@@ -80,10 +80,10 @@
(function (_ [offset tape])
(case (/.nth offset tape)
(#.Some output)
- (#try.Success [[("lux i64 +" 1 offset) tape] (/.from-code output)])
+ (#try.Success [[("lux i64 +" 1 offset) tape] (/.from_code output)])
_
- (exception.throw ..cannot-parse []))))
+ (exception.throw ..cannot_parse []))))
(def: #export any!
{#.doc "Just returns the next character without applying any logic."}
@@ -96,7 +96,7 @@
#distance 1}])
_
- (exception.throw ..cannot-slice []))))
+ (exception.throw ..cannot_slice []))))
(template [<name> <type> <any>]
[(def: #export (<name> p)
@@ -108,13 +108,13 @@
(<any> input)
_
- (exception.throw ..expected-to-fail input))))]
+ (exception.throw ..expected_to_fail input))))]
[not Text ..any]
[not! Slice ..any!]
)
-(exception: #export (cannot-match {reference Text})
+(exception: #export (cannot_match {reference Text})
(exception.report
["Reference" (/.encode reference)]))
@@ -122,15 +122,15 @@
{#.doc "Lex a text if it matches the given sample."}
(-> Text (Parser Any))
(function (_ [offset tape])
- (case (/.index-of' reference offset tape)
+ (case (/.index_of' reference offset tape)
(#.Some where)
(if (n.= offset where)
(#try.Success [[("lux i64 +" (/.size reference) offset) tape]
[]])
- (exception.throw ..cannot-match [reference]))
+ (exception.throw ..cannot_match [reference]))
_
- (exception.throw ..cannot-match [reference]))))
+ (exception.throw ..cannot_match [reference]))))
(def: #export end!
{#.doc "Ensure the parser's input is empty."}
@@ -138,7 +138,7 @@
(function (_ (^@ input [offset tape]))
(if (n.= offset (/.size tape))
(#try.Success [input []])
- (exception.throw ..unconsumed-input input))))
+ (exception.throw ..unconsumed_input input))))
(def: #export peek
{#.doc "Lex the next character (without consuming it from the input)."}
@@ -146,12 +146,12 @@
(function (_ (^@ input [offset tape]))
(case (/.nth offset tape)
(#.Some output)
- (#try.Success [input (/.from-code output)])
+ (#try.Success [input (/.from_code output)])
_
- (exception.throw ..cannot-parse []))))
+ (exception.throw ..cannot_parse []))))
-(def: #export get-input
+(def: #export get_input
{#.doc "Get all of the remaining input (without consuming it)."}
(Parser Text)
(function (_ (^@ input [offset tape]))
@@ -163,7 +163,7 @@
(do //.monad
[char any
#let [char' (maybe.assume (/.nth 0 char))]
- _ (//.assert ($_ /\compose "Character is not within range: " (/.from-code bottom) "-" (/.from-code top))
+ _ (//.assert ($_ /\compose "Character is not within range: " (/.from_code bottom) "-" (/.from_code top))
(.and (n.>= bottom char')
(n.<= top char')))]
(wrap char)))
@@ -185,7 +185,7 @@
(Parser Text)
(//.either lower upper))
-(def: #export alpha-num
+(def: #export alpha_num
{#.doc "Only lex alphanumeric characters."}
(Parser Text)
(//.either alpha decimal))
@@ -202,39 +202,39 @@
[(exception: #export (<name> {options Text} {character Char})
(exception.report
["Options" (/.encode options)]
- ["Character" (/.encode (/.from-code character))]))]
+ ["Character" (/.encode (/.from_code character))]))]
- [character-should-be]
- [character-should-not-be]
+ [character_should_be]
+ [character_should_not_be]
)
-(template [<name> <modifier> <exception> <description-modifier>]
+(template [<name> <modifier> <exception> <description_modifier>]
[(def: #export (<name> options)
- {#.doc (code.text ($_ /\compose "Only lex characters that are" <description-modifier> " part of a piece of text."))}
+ {#.doc (code.text ($_ /\compose "Only lex characters that are" <description_modifier> " part of a piece of text."))}
(-> Text (Parser Text))
(function (_ [offset tape])
(case (/.nth offset tape)
(#.Some output)
- (let [output' (/.from-code output)]
+ (let [output' (/.from_code output)]
(if (<modifier> (/.contains? output' options))
(#try.Success [[("lux i64 +" 1 offset) tape] output'])
(exception.throw <exception> [options output])))
_
- (exception.throw ..cannot-parse []))))]
+ (exception.throw ..cannot_parse []))))]
- [one-of |> ..character-should-be ""]
- [none-of .not ..character-should-not-be " not"]
+ [one_of |> ..character_should_be ""]
+ [none_of .not ..character_should_not_be " not"]
)
-(template [<name> <modifier> <exception> <description-modifier>]
+(template [<name> <modifier> <exception> <description_modifier>]
[(def: #export (<name> options)
- {#.doc (code.text ($_ /\compose "Only lex characters that are" <description-modifier> " part of a piece of text."))}
+ {#.doc (code.text ($_ /\compose "Only lex characters that are" <description_modifier> " part of a piece of text."))}
(-> Text (Parser Slice))
(function (_ [offset tape])
(case (/.nth offset tape)
(#.Some output)
- (let [output' (/.from-code output)]
+ (let [output' (/.from_code output)]
(if (<modifier> (/.contains? output' options))
(#try.Success [[("lux i64 +" 1 offset) tape]
{#basis offset
@@ -242,15 +242,15 @@
(exception.throw <exception> [options output])))
_
- (exception.throw ..cannot-slice []))))]
+ (exception.throw ..cannot_slice []))))]
- [one-of! |> ..character-should-be ""]
- [none-of! .not ..character-should-not-be " not"]
+ [one_of! |> ..character_should_be ""]
+ [none_of! .not ..character_should_not_be " not"]
)
-(exception: #export (character-does-not-satisfy-predicate {character Char})
+(exception: #export (character_does_not_satisfy_predicate {character Char})
(exception.report
- ["Character" (/.encode (/.from-code character))]))
+ ["Character" (/.encode (/.from_code character))]))
(def: #export (satisfies p)
{#.doc "Only lex characters that satisfy a predicate."}
@@ -259,11 +259,11 @@
(case (/.nth offset tape)
(#.Some output)
(if (p output)
- (#try.Success [[("lux i64 +" 1 offset) tape] (/.from-code output)])
- (exception.throw ..character-does-not-satisfy-predicate [output]))
+ (#try.Success [[("lux i64 +" 1 offset) tape] (/.from_code output)])
+ (exception.throw ..character_does_not_satisfy_predicate [output]))
_
- (exception.throw ..cannot-parse []))))
+ (exception.throw ..cannot_parse []))))
(def: #export space
{#.doc "Only lex white-space."}
@@ -284,9 +284,9 @@
[right::basis right::distance] right]
(wrap [left::basis ("lux i64 +" left::distance right::distance)])))
-(template [<name> <base> <doc-modifier>]
+(template [<name> <base> <doc_modifier>]
[(def: #export (<name> parser)
- {#.doc (code.text ($_ /\compose "Lex " <doc-modifier> " characters as a single continuous text."))}
+ {#.doc (code.text ($_ /\compose "Lex " <doc_modifier> " characters as a single continuous text."))}
(-> (Parser Text) (Parser Text))
(|> parser <base> (\ //.monad map /.concat)))]
@@ -294,36 +294,36 @@
[many //.many "many"]
)
-(template [<name> <base> <doc-modifier>]
+(template [<name> <base> <doc_modifier>]
[(def: #export (<name> parser)
- {#.doc (code.text ($_ /\compose "Lex " <doc-modifier> " characters as a single continuous text."))}
+ {#.doc (code.text ($_ /\compose "Lex " <doc_modifier> " characters as a single continuous text."))}
(-> (Parser Slice) (Parser Slice))
- (with-slices (<base> parser)))]
+ (with_slices (<base> parser)))]
[some! //.some "some"]
[many! //.many "many"]
)
-(template [<name> <base> <doc-modifier>]
+(template [<name> <base> <doc_modifier>]
[(def: #export (<name> amount parser)
- {#.doc (code.text ($_ /\compose "Lex " <doc-modifier> " N characters."))}
+ {#.doc (code.text ($_ /\compose "Lex " <doc_modifier> " N characters."))}
(-> Nat (Parser Text) (Parser Text))
(|> parser (<base> amount) (\ //.monad map /.concat)))]
[exactly //.exactly "exactly"]
- [at-most //.at-most "at most"]
- [at-least //.at-least "at least"]
+ [at_most //.at_most "at most"]
+ [at_least //.at_least "at least"]
)
-(template [<name> <base> <doc-modifier>]
+(template [<name> <base> <doc_modifier>]
[(def: #export (<name> amount parser)
- {#.doc (code.text ($_ /\compose "Lex " <doc-modifier> " N characters."))}
+ {#.doc (code.text ($_ /\compose "Lex " <doc_modifier> " N characters."))}
(-> Nat (Parser Slice) (Parser Slice))
- (with-slices (<base> amount parser)))]
+ (with_slices (<base> amount parser)))]
[exactly! //.exactly "exactly"]
- [at-most! //.at-most "at most"]
- [at-least! //.at-least "at least"]
+ [at_most! //.at_most "at most"]
+ [at_least! //.at_least "at least"]
)
(def: #export (between from to parser)
@@ -334,7 +334,7 @@
(def: #export (between! from to parser)
{#.doc "Lex between N and M characters."}
(-> Nat Nat (Parser Slice) (Parser Slice))
- (with-slices (//.between from to parser)))
+ (with_slices (//.between from to parser)))
(def: #export (enclosed [start end] parser)
(All [a] (-> [Text Text] (Parser a) (Parser a)))
@@ -342,16 +342,16 @@
(//.before (this end))
(//.after (this start))))
-(def: #export (local local-input parser)
+(def: #export (local local_input parser)
{#.doc "Run a parser with the given input, instead of the real one."}
(All [a] (-> Text (Parser a) (Parser a)))
- (function (_ real-input)
- (case (..run parser local-input)
+ (function (_ real_input)
+ (case (..run parser local_input)
(#try.Failure error)
(#try.Failure error)
(#try.Success value)
- (#try.Success [real-input value]))))
+ (#try.Success [real_input value]))))
(def: #export (slice parser)
(-> (Parser Slice) (Parser Text))
@@ -363,7 +363,7 @@
(#try.Success [input output])
#.None
- (exception.throw ..cannot-slice [])))))
+ (exception.throw ..cannot_slice [])))))
(def: #export (embed structured text)
(All [s a]
diff --git a/stdlib/source/lux/control/parser/type.lux b/stdlib/source/lux/control/parser/type.lux
index 8ed5004fe..32329abbe 100644
--- a/stdlib/source/lux/control/parser/type.lux
+++ b/stdlib/source/lux/control/parser/type.lux
@@ -25,16 +25,16 @@
(exception.report
["Type" (%.type type)]))]
- [not-existential]
- [not-recursive]
- [not-named]
- [not-parameter]
- [unknown-parameter]
- [not-function]
- [not-application]
- [not-polymorphic]
- [not-variant]
- [not-tuple]
+ [not_existential]
+ [not_recursive]
+ [not_named]
+ [not_parameter]
+ [unknown_parameter]
+ [not_function]
+ [not_application]
+ [not_polymorphic]
+ [not_variant]
+ [not_tuple]
)
(template [<name>]
@@ -43,17 +43,17 @@
["Expected" (%.type expected)]
["Actual" (%.type actual)]))]
- [types-do-not-match]
- [wrong-parameter]
+ [types_do_not_match]
+ [wrong_parameter]
)
-(exception: #export empty-input)
+(exception: #export empty_input)
-(exception: #export (unconsumed-input {remaining (List Type)})
+(exception: #export (unconsumed_input {remaining (List Type)})
(exception.report
["Types" (|> remaining
- (list\map (|>> %.type (format text.new-line "* ")))
- (text.join-with ""))]))
+ (list\map (|>> %.type (format text.new_line "* ")))
+ (text.join_with ""))]))
(type: #export Env
(Dictionary Nat [Type Code]))
@@ -77,7 +77,7 @@
(#try.Success output)
_
- (exception.throw ..unconsumed-input remaining))))
+ (exception.throw ..unconsumed_input remaining))))
(def: #export (run poly type)
(All [a] (-> (Parser a) Type (Try a)))
@@ -88,7 +88,7 @@
(.function (_ [env inputs])
(#try.Success [[env inputs] env])))
-(def: (with-env temp poly)
+(def: (with_env temp poly)
(All [a] (-> Env (Parser a) (Parser a)))
(.function (_ [env inputs])
(case (//.run poly [temp inputs])
@@ -103,7 +103,7 @@
(.function (_ [env inputs])
(case inputs
#.Nil
- (exception.throw ..empty-input [])
+ (exception.throw ..empty_input [])
(#.Cons headT tail)
(#try.Success [[env inputs] headT]))))
@@ -113,32 +113,32 @@
(.function (_ [env inputs])
(case inputs
#.Nil
- (exception.throw ..empty-input [])
+ (exception.throw ..empty_input [])
(#.Cons headT tail)
(#try.Success [[env tail] headT]))))
(def: #export (local types poly)
(All [a] (-> (List Type) (Parser a) (Parser a)))
- (.function (_ [env pass-through])
+ (.function (_ [env pass_through])
(case (run' env poly types)
(#try.Failure error)
(#try.Failure error)
(#try.Success output)
- (#try.Success [[env pass-through] output]))))
+ (#try.Success [[env pass_through] output]))))
(def: (label idx)
(-> Nat Code)
- (code.local-identifier ($_ text\compose "label" text.tab (n\encode idx))))
+ (code.local_identifier ($_ text\compose "label" text.tab (n\encode idx))))
-(def: #export (with-extension type poly)
+(def: #export (with_extension type poly)
(All [a] (-> Type (Parser a) (Parser [Code a])))
(.function (_ [env inputs])
- (let [current-id (dictionary.size env)
- g!var (label current-id)]
+ (let [current_id (dictionary.size env)
+ g!var (label current_id)]
(case (//.run poly
- [(dictionary.put current-id [type g!var] env)
+ [(dictionary.put current_id [type g!var] env)
inputs])
(#try.Failure error)
(#try.Failure error)
@@ -151,78 +151,78 @@
(All [a] (-> (Parser a) (Parser a)))
(do //.monad
[headT ..any]
- (let [members (<flattener> (type.un-name headT))]
+ (let [members (<flattener> (type.un_name headT))]
(if (n.> 1 (list.size members))
(local members poly)
(//.fail (exception.construct <exception> headT))))))]
- [variant type.flatten-variant #.Sum ..not-variant]
- [tuple type.flatten-tuple #.Product ..not-tuple]
+ [variant type.flatten_variant #.Sum ..not_variant]
+ [tuple type.flatten_tuple #.Product ..not_tuple]
)
(def: polymorphic'
(Parser [Nat Type])
(do //.monad
[headT any
- #let [[num-arg bodyT] (type.flatten-univ-q (type.un-name headT))]]
- (if (n.= 0 num-arg)
- (//.fail (exception.construct ..not-polymorphic headT))
- (wrap [num-arg bodyT]))))
+ #let [[num_arg bodyT] (type.flatten_univ_q (type.un_name headT))]]
+ (if (n.= 0 num_arg)
+ (//.fail (exception.construct ..not_polymorphic headT))
+ (wrap [num_arg bodyT]))))
(def: #export (polymorphic poly)
(All [a] (-> (Parser a) (Parser [Code (List Code) a])))
(do {! //.monad}
[headT any
funcI (\ ! map dictionary.size ..env)
- [num-args non-poly] (local (list headT) ..polymorphic')
+ [num_args non_poly] (local (list headT) ..polymorphic')
env ..env
#let [funcL (label funcI)
- [all-varsL env'] (loop [current-arg 0
+ [all_varsL env'] (loop [current_arg 0
env' env
- all-varsL (: (List Code) (list))]
- (if (n.< num-args current-arg)
- (if (n.= 0 current-arg)
+ all_varsL (: (List Code) (list))]
+ (if (n.< num_args current_arg)
+ (if (n.= 0 current_arg)
(let [varL (label (inc funcI))]
- (recur (inc current-arg)
+ (recur (inc current_arg)
(|> env'
(dictionary.put funcI [headT funcL])
(dictionary.put (inc funcI) [(#.Parameter (inc funcI)) varL]))
- (#.Cons varL all-varsL)))
- (let [partialI (|> current-arg (n.* 2) (n.+ funcI))
- partial-varI (inc partialI)
- partial-varL (label partial-varI)
- partialC (` ((~ funcL) (~+ (|> (list.indices num-args)
+ (#.Cons varL all_varsL)))
+ (let [partialI (|> current_arg (n.* 2) (n.+ funcI))
+ partial_varI (inc partialI)
+ partial_varL (label partial_varI)
+ partialC (` ((~ funcL) (~+ (|> (list.indices num_args)
(list\map (|>> (n.* 2) inc (n.+ funcI) label))
list.reverse))))]
- (recur (inc current-arg)
+ (recur (inc current_arg)
(|> env'
(dictionary.put partialI [.Nothing partialC])
- (dictionary.put partial-varI [(#.Parameter partial-varI) partial-varL]))
- (#.Cons partial-varL all-varsL))))
- [all-varsL env']))]]
- (<| (with-env env')
- (local (list non-poly))
+ (dictionary.put partial_varI [(#.Parameter partial_varI) partial_varL]))
+ (#.Cons partial_varL all_varsL))))
+ [all_varsL env']))]]
+ (<| (with_env env')
+ (local (list non_poly))
(do !
[output poly]
- (wrap [funcL all-varsL output])))))
+ (wrap [funcL all_varsL output])))))
-(def: #export (function in-poly out-poly)
+(def: #export (function in_poly out_poly)
(All [i o] (-> (Parser i) (Parser o) (Parser [i o])))
(do //.monad
[headT any
- #let [[inputsT outputT] (type.flatten-function (type.un-name headT))]]
+ #let [[inputsT outputT] (type.flatten_function (type.un_name headT))]]
(if (n.> 0 (list.size inputsT))
- (//.and (local inputsT in-poly)
- (local (list outputT) out-poly))
- (//.fail (exception.construct ..not-function headT)))))
+ (//.and (local inputsT in_poly)
+ (local (list outputT) out_poly))
+ (//.fail (exception.construct ..not_function headT)))))
(def: #export (apply poly)
(All [a] (-> (Parser a) (Parser a)))
(do //.monad
[headT any
- #let [[funcT paramsT] (type.flatten-application (type.un-name headT))]]
+ #let [[funcT paramsT] (type.flatten_application (type.un_name headT))]]
(if (n.= 0 (list.size paramsT))
- (//.fail (exception.construct ..not-application headT))
+ (//.fail (exception.construct ..not_application headT))
(..local (#.Cons funcT paramsT) poly))))
(template [<name> <test>]
@@ -232,19 +232,19 @@
[actual any]
(if (<test> expected actual)
(wrap [])
- (//.fail (exception.construct ..types-do-not-match [expected actual])))))]
+ (//.fail (exception.construct ..types_do_not_match [expected actual])))))]
[exactly type\=]
[sub check.checks?]
[super (function.flip check.checks?)]
)
-(def: #export (adjusted-idx env idx)
+(def: #export (adjusted_idx env idx)
(-> Env Nat Nat)
- (let [env-level (n./ 2 (dictionary.size env))
- parameter-level (n./ 2 idx)
- parameter-idx (n.% 2 idx)]
- (|> env-level dec (n.- parameter-level) (n.* 2) (n.+ parameter-idx))))
+ (let [env_level (n./ 2 (dictionary.size env))
+ parameter_level (n./ 2 idx)
+ parameter_idx (n.% 2 idx)]
+ (|> env_level dec (n.- parameter_level) (n.* 2) (n.+ parameter_idx))))
(def: #export parameter
(Parser Code)
@@ -253,15 +253,15 @@
headT any]
(case headT
(#.Parameter idx)
- (case (dictionary.get (adjusted-idx env idx) env)
- (#.Some [poly-type poly-code])
- (wrap poly-code)
+ (case (dictionary.get (adjusted_idx env idx) env)
+ (#.Some [poly_type poly_code])
+ (wrap poly_code)
#.None
- (//.fail (exception.construct ..unknown-parameter headT)))
+ (//.fail (exception.construct ..unknown_parameter headT)))
_
- (//.fail (exception.construct ..not-parameter headT)))))
+ (//.fail (exception.construct ..not_parameter headT)))))
(def: #export (parameter! id)
(-> Nat (Parser Any))
@@ -270,23 +270,23 @@
headT any]
(case headT
(#.Parameter idx)
- (if (n.= id (adjusted-idx env idx))
+ (if (n.= id (adjusted_idx env idx))
(wrap [])
- (//.fail (exception.construct ..wrong-parameter [(#.Parameter id) headT])))
+ (//.fail (exception.construct ..wrong_parameter [(#.Parameter id) headT])))
_
- (//.fail (exception.construct ..not-parameter headT)))))
+ (//.fail (exception.construct ..not_parameter headT)))))
(def: #export existential
(Parser Nat)
(do //.monad
[headT any]
(case headT
- (#.Ex ex-id)
- (wrap ex-id)
+ (#.Ex ex_id)
+ (wrap ex_id)
_
- (//.fail (exception.construct ..not-existential headT)))))
+ (//.fail (exception.construct ..not_existential headT)))))
(def: #export named
(Parser [Name Type])
@@ -297,7 +297,7 @@
(wrap [name anonymousT])
_
- (//.fail (exception.construct ..not-named inputT)))))
+ (//.fail (exception.construct ..not_named inputT)))))
(template: (|nothing|)
(#.Named ["lux" "Nothing"]
@@ -308,33 +308,33 @@
(All [a] (-> (Parser a) (Parser [Code a])))
(do {! //.monad}
[headT any]
- (case (type.un-name headT)
+ (case (type.un_name headT)
(^ (#.Apply (|nothing|) (#.UnivQ _ headT')))
(do !
[[recT _ output] (|> poly
- (with-extension .Nothing)
- (with-extension headT)
+ (with_extension .Nothing)
+ (with_extension headT)
(local (list headT')))]
(wrap [recT output]))
_
- (//.fail (exception.construct ..not-recursive headT)))))
+ (//.fail (exception.construct ..not_recursive headT)))))
-(def: #export recursive-self
+(def: #export recursive_self
(Parser Code)
(do //.monad
[env ..env
headT any]
- (case (type.un-name headT)
- (^multi (^ (#.Apply (|nothing|) (#.Parameter funcT-idx)))
- (n.= 0 (adjusted-idx env funcT-idx))
- [(dictionary.get 0 env) (#.Some [self-type self-call])])
- (wrap self-call)
+ (case (type.un_name headT)
+ (^multi (^ (#.Apply (|nothing|) (#.Parameter funcT_idx)))
+ (n.= 0 (adjusted_idx env funcT_idx))
+ [(dictionary.get 0 env) (#.Some [self_type self_call])])
+ (wrap self_call)
_
- (//.fail (exception.construct ..not-recursive headT)))))
+ (//.fail (exception.construct ..not_recursive headT)))))
-(def: #export recursive-call
+(def: #export recursive_call
(Parser Code)
(do {! //.monad}
[env ..env
diff --git a/stdlib/source/lux/control/parser/xml.lux b/stdlib/source/lux/control/parser/xml.lux
index bc8c6ad93..3b9732ae5 100644
--- a/stdlib/source/lux/control/parser/xml.lux
+++ b/stdlib/source/lux/control/parser/xml.lux
@@ -19,20 +19,20 @@
(type: #export (Parser a)
(//.Parser (List XML) a))
-(exception: #export empty-input)
-(exception: #export unexpected-input)
+(exception: #export empty_input)
+(exception: #export unexpected_input)
-(exception: #export (wrong-tag {expected Tag} {actual Tag})
+(exception: #export (wrong_tag {expected Tag} {actual Tag})
(exception.report
["Expected" (%.text (/.tag expected))]
["Actual" (%.text (/.tag actual))]))
-(exception: #export (unknown-attribute {expected Attribute} {available (List Attribute)})
+(exception: #export (unknown_attribute {expected Attribute} {available (List Attribute)})
(exception.report
["Expected" (%.text (/.attribute expected))]
["Available" (exception.enumerate (|>> /.attribute %.text) available)]))
-(exception: #export (unconsumed-inputs {inputs (List XML)})
+(exception: #export (unconsumed_inputs {inputs (List XML)})
(exception.report
["Inputs" (exception.enumerate (\ /.codec encode) inputs)]))
@@ -41,7 +41,7 @@
(function (_ docs)
(case docs
#.Nil
- (exception.throw ..empty-input [])
+ (exception.throw ..empty_input [])
(#.Cons head tail)
(case head
@@ -49,36 +49,36 @@
(#try.Success [tail value])
(#/.Node _)
- (exception.throw ..unexpected-input [])))))
+ (exception.throw ..unexpected_input [])))))
(def: #export (node expected)
(-> Tag (Parser Any))
(function (_ docs)
(case docs
#.Nil
- (exception.throw ..empty-input [])
+ (exception.throw ..empty_input [])
(#.Cons head _)
(case head
(#/.Text _)
- (exception.throw ..unexpected-input [])
+ (exception.throw ..unexpected_input [])
(#/.Node actual _attributes _children)
(if (name\= expected actual)
(#try.Success [docs []])
- (exception.throw ..wrong-tag [expected actual]))))))
+ (exception.throw ..wrong_tag [expected actual]))))))
(def: #export tag
(Parser Tag)
(function (_ docs)
(case docs
#.Nil
- (exception.throw ..empty-input [])
+ (exception.throw ..empty_input [])
(#.Cons head _)
(case head
(#/.Text _)
- (exception.throw ..unexpected-input [])
+ (exception.throw ..unexpected_input [])
(#/.Node tag _attributes _children)
(#try.Success [docs tag])))))
@@ -88,17 +88,17 @@
(function (_ docs)
(case docs
#.Nil
- (exception.throw ..empty-input [])
+ (exception.throw ..empty_input [])
(#.Cons head _)
(case head
(#/.Text _)
- (exception.throw ..unexpected-input [])
+ (exception.throw ..unexpected_input [])
(#/.Node tag attributes children)
(case (dictionary.get name attributes)
#.None
- (exception.throw ..unknown-attribute [name (dictionary.keys attributes)])
+ (exception.throw ..unknown_attribute [name (dictionary.keys attributes)])
(#.Some value)
(#try.Success [docs value]))))))
@@ -109,7 +109,7 @@
(#try.Success [remaining output])
(if (list.empty? remaining)
(#try.Success output)
- (exception.throw ..unconsumed-inputs remaining))
+ (exception.throw ..unconsumed_inputs remaining))
(#try.Failure error)
(#try.Failure error)))
@@ -119,12 +119,12 @@
(function (_ docs)
(case docs
#.Nil
- (exception.throw ..empty-input [])
+ (exception.throw ..empty_input [])
(#.Cons head tail)
(case head
(#/.Text _)
- (exception.throw ..unexpected-input [])
+ (exception.throw ..unexpected_input [])
(#/.Node _tag _attributes children)
(do try.monad
@@ -136,7 +136,7 @@
(function (_ docs)
(case docs
#.Nil
- (exception.throw ..empty-input [])
+ (exception.throw ..empty_input [])
(#.Cons head tail)
(#try.Success [tail []]))))