aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/control/parser
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/control/parser.lux121
-rw-r--r--stdlib/source/lux/control/parser/binary.lux30
-rw-r--r--stdlib/source/lux/control/parser/cli.lux47
-rw-r--r--stdlib/source/lux/control/parser/code.lux73
-rw-r--r--stdlib/source/lux/control/parser/json.lux36
-rw-r--r--stdlib/source/lux/control/parser/synthesis.lux28
-rw-r--r--stdlib/source/lux/control/parser/text.lux80
-rw-r--r--stdlib/source/lux/control/parser/tree.lux18
-rw-r--r--stdlib/source/lux/control/parser/type.lux48
-rw-r--r--stdlib/source/lux/control/parser/xml.lux24
10 files changed, 254 insertions, 251 deletions
diff --git a/stdlib/source/lux/control/parser.lux b/stdlib/source/lux/control/parser.lux
index 6642310b9..66799e067 100644
--- a/stdlib/source/lux/control/parser.lux
+++ b/stdlib/source/lux/control/parser.lux
@@ -5,15 +5,16 @@
[apply (#+ Apply)]
[monad (#+ Monad do)]
[codec (#+ Codec)]]
+ [control
+ ["." try (#+ Try)]]
[data
[collection
["." list ("#@." functor monoid)]]
- ["." product]
- ["." error (#+ Error)]]])
+ ["." product]]])
(type: #export (Parser s a)
{#.doc "A generic parser."}
- (-> s (Error [s a])))
+ (-> s (Try [s a])))
(structure: #export functor
(All [s] (Functor (Parser s)))
@@ -21,11 +22,11 @@
(def: (map f ma)
(function (_ input)
(case (ma input)
- (#error.Failure msg)
- (#error.Failure msg)
+ (#try.Failure msg)
+ (#try.Failure msg)
- (#error.Success [input' a])
- (#error.Success [input' (f a)])))))
+ (#try.Success [input' a])
+ (#try.Success [input' (f a)])))))
(structure: #export apply
(All [s] (Apply (Parser s)))
@@ -35,16 +36,16 @@
(def: (apply ff fa)
(function (_ input)
(case (ff input)
- (#error.Success [input' f])
+ (#try.Success [input' f])
(case (fa input')
- (#error.Success [input'' a])
- (#error.Success [input'' (f a)])
+ (#try.Success [input'' a])
+ (#try.Success [input'' (f a)])
- (#error.Failure msg)
- (#error.Failure msg))
+ (#try.Failure msg)
+ (#try.Failure msg))
- (#error.Failure msg)
- (#error.Failure msg)))))
+ (#try.Failure msg)
+ (#try.Failure msg)))))
(structure: #export monad
(All [s] (Monad (Parser s)))
@@ -53,15 +54,15 @@
(def: (wrap x)
(function (_ input)
- (#error.Success [input x])))
+ (#try.Success [input x])))
(def: (join mma)
(function (_ input)
(case (mma input)
- (#error.Failure msg)
- (#error.Failure msg)
+ (#try.Failure msg)
+ (#try.Failure msg)
- (#error.Success [input' ma])
+ (#try.Success [input' ma])
(ma input')))))
(def: #export (assert message test)
@@ -69,8 +70,8 @@
(All [s] (-> Text Bit (Parser s Any)))
(function (_ input)
(if test
- (#error.Success [input []])
- (#error.Failure message))))
+ (#try.Success [input []])
+ (#try.Failure message))))
(def: #export (maybe p)
{#.doc "Optionality combinator."}
@@ -78,15 +79,15 @@
(-> (Parser s a) (Parser s (Maybe a))))
(function (_ input)
(case (p input)
- (#error.Failure _)
- (#error.Success [input #.None])
+ (#try.Failure _)
+ (#try.Success [input #.None])
- (#error.Success [input' x])
- (#error.Success [input' (#.Some x)]))))
+ (#try.Success [input' x])
+ (#try.Success [input' (#.Some x)]))))
(def: #export (run p input)
(All [s a]
- (-> (Parser s a) s (Error [s a])))
+ (-> (Parser s a) s (Try [s a])))
(p input))
(def: #export (some p)
@@ -95,10 +96,10 @@
(-> (Parser s a) (Parser s (List a))))
(function (_ input)
(case (p input)
- (#error.Failure _)
- (#error.Success [input (list)])
+ (#try.Failure _)
+ (#try.Success [input (list)])
- (#error.Success [input' x])
+ (#try.Success [input' x])
(run (do ..monad
[xs (some p)]
(wrap (list& x xs)))
@@ -128,10 +129,10 @@
(-> (Parser s a) (Parser s b) (Parser s (| a b))))
(function (_ tokens)
(case (p1 tokens)
- (#error.Success [tokens' x1])
- (#error.Success [tokens' (0 x1)])
+ (#try.Success [tokens' x1])
+ (#try.Success [tokens' (0 x1)])
- (#error.Failure _)
+ (#try.Failure _)
(run (do ..monad
[x2 p2]
(wrap (1 x2)))
@@ -144,7 +145,7 @@
(-> (Parser s a) (Parser s a) (Parser s a)))
(function (_ tokens)
(case (pl tokens)
- (#error.Failure _)
+ (#try.Failure _)
(pr tokens)
output
@@ -175,10 +176,10 @@
(if (n/> 0 n)
(function (_ input)
(case (p input)
- (#error.Failure msg)
- (#error.Success [input (list)])
+ (#try.Failure msg)
+ (#try.Success [input (list)])
- (#error.Success [input' x])
+ (#try.Success [input' x])
(run (do ..monad
[xs (at-most (dec n) p)]
(wrap (#.Cons x xs)))
@@ -213,42 +214,42 @@
(All [s a] (-> (Parser s a) (Parser s Any)))
(function (_ input)
(case (p input)
- (#error.Failure msg)
- (#error.Success [input []])
+ (#try.Failure msg)
+ (#try.Success [input []])
_
- (#error.Failure "Expected to fail; yet succeeded."))))
+ (#try.Failure "Expected to fail; yet succeeded."))))
(def: #export (fail message)
(All [s a] (-> Text (Parser s a)))
(function (_ input)
- (#error.Failure message)))
+ (#try.Failure message)))
(def: #export (lift operation)
- (All [s a] (-> (Error a) (Parser s a)))
+ (All [s a] (-> (Try a) (Parser s a)))
(function (_ input)
(case operation
- (#error.Success output)
- (#error.Success [input output])
+ (#try.Success output)
+ (#try.Success [input output])
- (#error.Failure error)
- (#error.Failure error))))
+ (#try.Failure error)
+ (#try.Failure error))))
(def: #export (default value parser)
{#.doc "If the given parser fails, returns the default value."}
(All [s a] (-> a (Parser s a) (Parser s a)))
(function (_ input)
(case (parser input)
- (#error.Failure error)
- (#error.Success [input value])
+ (#try.Failure error)
+ (#try.Success [input value])
- (#error.Success [input' output])
- (#error.Success [input' output]))))
+ (#try.Success [input' output])
+ (#try.Success [input' output]))))
(def: #export remaining
(All [s] (Parser s s))
(function (_ inputs)
- (#error.Success [inputs inputs])))
+ (#try.Success [inputs inputs])))
(def: #export (rec parser)
{#.doc "Combinator for recursive parser."}
@@ -280,23 +281,23 @@
(All [s a] (-> (Parser s a) (Parser s Bit)))
(function (_ input)
(case (parser input)
- (#error.Failure error)
- (#error.Success [input false])
+ (#try.Failure error)
+ (#try.Success [input false])
- (#error.Success [input' _])
- (#error.Success [input' true]))))
+ (#try.Success [input' _])
+ (#try.Success [input' true]))))
(def: #export (codec Codec<a,z> parser)
(All [s a z] (-> (Codec a z) (Parser s a) (Parser s z)))
(function (_ input)
(case (parser input)
- (#error.Failure error)
- (#error.Failure error)
+ (#try.Failure error)
+ (#try.Failure error)
- (#error.Success [input' to-decode])
+ (#try.Success [input' to-decode])
(case (:: Codec<a,z> decode to-decode)
- (#error.Failure error)
- (#error.Failure error)
+ (#try.Failure error)
+ (#try.Failure error)
- (#error.Success value)
- (#error.Success [input' value])))))
+ (#try.Success value)
+ (#try.Success [input' value])))))
diff --git a/stdlib/source/lux/control/parser/binary.lux b/stdlib/source/lux/control/parser/binary.lux
index 89a9c709d..5f8ccc122 100644
--- a/stdlib/source/lux/control/parser/binary.lux
+++ b/stdlib/source/lux/control/parser/binary.lux
@@ -4,9 +4,9 @@
[abstract
[monad (#+ do)]]
[control
+ ["." try (#+ Try)]
["." exception (#+ exception:)]]
[data
- ["." error (#+ Error)]
["." binary (#+ Binary)]
[number
["." frac]]
@@ -28,15 +28,15 @@
["Read bytes" (%.nat read)]))
(def: #export (run parser input)
- (All [a] (-> (Parser a) Binary (Error a)))
+ (All [a] (-> (Parser a) Binary (Try a)))
(case (parser [0 input])
- (#error.Failure msg)
- (#error.Failure msg)
+ (#try.Failure msg)
+ (#try.Failure msg)
- (#error.Success [[end _] output])
+ (#try.Success [[end _] output])
(let [length (binary.size input)]
(if (n/= end length)
- (#error.Success output)
+ (#try.Success output)
(exception.throw ..binary-was-not-fully-read [length end])))))
(type: #export Size Nat)
@@ -51,11 +51,11 @@
(Parser (I64 Any))
(function (_ [offset binary])
(case (<read> offset binary)
- (#error.Success data)
- (#error.Success [(n/+ <size> offset) binary] data)
+ (#try.Success data)
+ (#try.Success [(n/+ <size> offset) binary] data)
- (#error.Failure error)
- (#error.Failure error))))]
+ (#try.Failure error)
+ (#try.Failure error))))]
[bits/8 ..size/8 binary.read/8]
[bits/16 ..size/16 binary.read/16]
@@ -91,18 +91,18 @@
(Parser Bit)
(function (_ [offset binary])
(case (binary.read/8 offset binary)
- (#error.Success data)
+ (#try.Success data)
(case (: Nat data)
(^template [<nat> <bit>]
- <nat> (#error.Success [(inc offset) binary] <bit>))
+ <nat> (#try.Success [(inc offset) binary] <bit>))
([0 #0]
[1 #1])
_
(exception.throw ..invalid-tag [2 data]))
- (#error.Failure error)
- (#error.Failure error))))
+ (#try.Failure error)
+ (#try.Failure error))))
(def: #export nat (Parser Nat) (//@map .nat ..bits/64))
(def: #export int (Parser Int) (//@map .int ..bits/64))
@@ -118,7 +118,7 @@
(do //.monad
[size (//@map .nat <bits>)]
(function (_ [offset binary])
- (do error.monad
+ (do try.monad
[#let [end (n/+ size offset)]
output (binary.slice offset (.dec end) binary)]
(wrap [[end binary] output])))))]
diff --git a/stdlib/source/lux/control/parser/cli.lux b/stdlib/source/lux/control/parser/cli.lux
index fddea13d7..01c75a955 100644
--- a/stdlib/source/lux/control/parser/cli.lux
+++ b/stdlib/source/lux/control/parser/cli.lux
@@ -3,12 +3,13 @@
["@" target]
[abstract
[monad (#+ do)]]
+ [control
+ ["." try (#+ Try)]]
[data
[collection
["." list ("#@." monoid monad)]]
["." text ("#@." equivalence)
- ["%" format (#+ format)]]
- ["." error (#+ Error)]]
+ ["%" format (#+ format)]]]
[macro (#+ with-gensyms)
["." code]
[syntax (#+ syntax:)]]]
@@ -24,18 +25,18 @@
(//.Parser (List Text) a))
(def: #export (run parser inputs)
- (All [a] (-> (Parser a) (List Text) (Error a)))
+ (All [a] (-> (Parser a) (List Text) (Try a)))
(case (//.run parser inputs)
- (#error.Success [remaining output])
+ (#try.Success [remaining output])
(case remaining
#.Nil
- (#error.Success output)
+ (#try.Success output)
_
- (#error.Failure (format "Remaining CLI inputs: " (text.join-with " " remaining))))
+ (#try.Failure (format "Remaining CLI inputs: " (text.join-with " " remaining))))
- (#error.Failure error)
- (#error.Failure error)))
+ (#try.Failure try)
+ (#try.Failure try)))
(def: #export any
{#.doc "Just returns the next input without applying any logic."}
@@ -43,16 +44,16 @@
(function (_ inputs)
(case inputs
(#.Cons arg inputs')
- (#error.Success [inputs' arg])
+ (#try.Success [inputs' arg])
_
- (#error.Failure "Cannot parse empty arguments."))))
+ (#try.Failure "Cannot parse empty arguments."))))
(def: #export (parse parser)
{#.doc "Parses the next input with a parsing function."}
- (All [a] (-> (-> Text (Error a)) (Parser a)))
+ (All [a] (-> (-> Text (Try a)) (Parser a)))
(function (_ inputs)
- (do error.monad
+ (do try.monad
[[remaining raw] (any inputs)
output (parser raw)]
(wrap [remaining output]))))
@@ -61,11 +62,11 @@
{#.doc "Checks that a token is in the inputs."}
(-> Text (Parser Any))
(function (_ inputs)
- (do error.monad
+ (do try.monad
[[remaining raw] (any inputs)]
(if (text@= reference raw)
(wrap [remaining []])
- (error.fail (format "Missing token: '" reference "'"))))))
+ (try.fail (format "Missing token: '" reference "'"))))))
(def: #export (somewhere cli)
{#.doc "Given a parser, tries to parse it somewhere in the inputs (i.e. not necessarily parsing the immediate inputs)."}
@@ -73,16 +74,16 @@
(function (_ inputs)
(loop [immediate inputs]
(case (//.run cli immediate)
- (#error.Success [remaining output])
- (#error.Success [remaining output])
+ (#try.Success [remaining output])
+ (#try.Success [remaining output])
- (#error.Failure error)
+ (#try.Failure try)
(case immediate
#.Nil
- (#error.Failure error)
+ (#try.Failure try)
(#.Cons to-omit immediate')
- (do error.monad
+ (do try.monad
[[remaining output] (recur immediate')]
(wrap [(#.Cons to-omit remaining)
output])))))))
@@ -92,8 +93,8 @@
(Parser Any)
(function (_ inputs)
(case inputs
- #.Nil (#error.Success [inputs []])
- _ (#error.Failure (format "Unknown parameters: " (text.join-with " " inputs))))))
+ #.Nil (#try.Success [inputs []])
+ _ (#try.Failure (format "Unknown parameters: " (text.join-with " " inputs))))))
(def: #export (named name value)
(All [a] (-> Text (Parser a) (Parser a)))
@@ -168,10 +169,10 @@
(` process.run!)))))]
((~' wrap) (~ g!output))))))
(~ g!args))
- (#error.Success [(~ g!_) (~ g!output)])
+ (#try.Success [(~ g!_) (~ g!output)])
(~ g!output)
- (#error.Failure (~ g!message))
+ (#try.Failure (~ g!message))
(.error! (~ g!message))
))))
)))
diff --git a/stdlib/source/lux/control/parser/code.lux b/stdlib/source/lux/control/parser/code.lux
index 25009b447..33ff0abe2 100644
--- a/stdlib/source/lux/control/parser/code.lux
+++ b/stdlib/source/lux/control/parser/code.lux
@@ -2,10 +2,11 @@
[lux (#- nat int rev)
[abstract
["." monad (#+ do)]]
+ [control
+ ["." try (#+ Try)]]
[data
["." bit]
["." name]
- ["." error (#+ Error)]
[number
["." nat]
["." int]
@@ -38,18 +39,18 @@
(Parser Code)
(function (_ tokens)
(case tokens
- #.Nil (#error.Failure "There are no tokens to parse!")
- (#.Cons [t tokens']) (#error.Success [tokens' t]))))
+ #.Nil (#try.Failure "There are no tokens to parse!")
+ (#.Cons [t tokens']) (#try.Success [tokens' t]))))
(template [<query> <assertion> <type> <tag> <eq> <desc>]
- [(with-expansions [<error> (as-is (#error.Failure ($_ text@compose "Cannot parse " <desc> (remaining-inputs tokens))))]
+ [(with-expansions [<error> (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>)
(function (_ tokens)
(case tokens
(#.Cons [[_ (<tag> x)] tokens'])
- (#error.Success [tokens' x])
+ (#try.Success [tokens' x])
_
<error>)))
@@ -60,7 +61,7 @@
(case tokens
(#.Cons [[_ (<tag> actual)] tokens'])
(if (:: <eq> = expected actual)
- (#error.Success [tokens' []])
+ (#try.Success [tokens' []])
<error>)
_
@@ -83,12 +84,12 @@
(case tokens
(#.Cons [token tokens'])
(if (code@= ast token)
- (#error.Success [tokens' []])
- (#error.Failure ($_ text@compose "Expected a " (code.to-text ast) " but instead got " (code.to-text token)
- (remaining-inputs tokens))))
+ (#try.Success [tokens' []])
+ (#try.Failure ($_ text@compose "Expected a " (code.to-text ast) " but instead got " (code.to-text token)
+ (remaining-inputs tokens))))
_
- (#error.Failure "There are no tokens to parse!"))))
+ (#try.Failure "There are no tokens to parse!"))))
(template [<name> <tag> <desc>]
[(def: #export <name>
@@ -97,10 +98,10 @@
(function (_ tokens)
(case tokens
(#.Cons [[_ (<tag> ["" x])] tokens'])
- (#error.Success [tokens' x])
+ (#try.Success [tokens' x])
_
- (#error.Failure ($_ text@compose "Cannot parse local " <desc> (remaining-inputs tokens))))))]
+ (#try.Failure ($_ text@compose "Cannot parse local " <desc> (remaining-inputs tokens))))))]
[local-identifier #.Identifier "identifier"]
[ local-tag #.Tag "tag"]
@@ -115,11 +116,11 @@
(case tokens
(#.Cons [[_ (<tag> members)] tokens'])
(case (p members)
- (#error.Success [#.Nil x]) (#error.Success [tokens' x])
- _ (#error.Failure ($_ text@compose "Parser was expected to fully consume " <desc> (remaining-inputs tokens))))
+ (#try.Success [#.Nil x]) (#try.Success [tokens' x])
+ _ (#try.Failure ($_ text@compose "Parser was expected to fully consume " <desc> (remaining-inputs tokens))))
_
- (#error.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"]
@@ -133,59 +134,59 @@
(case tokens
(#.Cons [[_ (#.Record pairs)] tokens'])
(case (p (join-pairs pairs))
- (#error.Success [#.Nil x]) (#error.Success [tokens' x])
- _ (#error.Failure ($_ text@compose "Parser was expected to fully consume record" (remaining-inputs tokens))))
+ (#try.Success [#.Nil x]) (#try.Success [tokens' x])
+ _ (#try.Failure ($_ text@compose "Parser was expected to fully consume record" (remaining-inputs tokens))))
_
- (#error.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."}
(Parser Any)
(function (_ tokens)
(case tokens
- #.Nil (#error.Success [tokens []])
- _ (#error.Failure ($_ text@compose "Expected list of tokens to be empty!" (remaining-inputs tokens))))))
+ #.Nil (#try.Success [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."}
(Parser Bit)
(function (_ tokens)
(case tokens
- #.Nil (#error.Success [tokens #1])
- _ (#error.Success [tokens #0]))))
+ #.Nil (#try.Success [tokens #1])
+ _ (#try.Success [tokens #0]))))
(def: #export (lift outcome)
- (All [a] (-> (Error a) (Parser a)))
+ (All [a] (-> (Try a) (Parser a)))
(function (_ input)
(case outcome
- (#error.Failure error)
- (#error.Failure error)
+ (#try.Failure error)
+ (#try.Failure error)
- (#error.Success value)
- (#error.Success [input value])
+ (#try.Success value)
+ (#try.Success [input value])
)))
(def: #export (run syntax inputs)
- (All [a] (-> (Parser a) (List Code) (Error a)))
+ (All [a] (-> (Parser a) (List Code) (Try a)))
(case (syntax inputs)
- (#error.Failure error)
- (#error.Failure error)
+ (#try.Failure error)
+ (#try.Failure error)
- (#error.Success [unconsumed value])
+ (#try.Success [unconsumed value])
(case unconsumed
#.Nil
- (#error.Success value)
+ (#try.Success value)
_
- (#error.Failure (text@compose "Unconsumed inputs: "
- (|> (list@map code.to-text unconsumed)
- (text.join-with ", ")))))))
+ (#try.Failure (text@compose "Unconsumed inputs: "
+ (|> (list@map code.to-text unconsumed)
+ (text.join-with ", ")))))))
(def: #export (local inputs syntax)
{#.doc "Run a syntax parser with the given list of inputs, instead of the real ones."}
(All [a] (-> (List Code) (Parser a) (Parser a)))
(function (_ real)
- (do error.monad
+ (do try.monad
[value (run syntax inputs)]
(wrap [real value]))))
diff --git a/stdlib/source/lux/control/parser/json.lux b/stdlib/source/lux/control/parser/json.lux
index 1ef75eab4..ed1620627 100644
--- a/stdlib/source/lux/control/parser/json.lux
+++ b/stdlib/source/lux/control/parser/json.lux
@@ -3,10 +3,10 @@
[abstract
["." monad (#+ do)]]
[control
+ ["." try (#+ Try)]
["." exception (#+ exception:)]]
[data
["." bit]
- ["." error (#+ Error)]
["." text ("#@." equivalence monoid)]
[number
["." frac]]
@@ -31,23 +31,23 @@
(exception: #export empty-input)
(def: #export (run json parser)
- (All [a] (-> JSON (Parser a) (Error a)))
+ (All [a] (-> JSON (Parser a) (Try a)))
(case (//.run parser (list json))
- (#error.Success [remainder output])
+ (#try.Success [remainder output])
(case remainder
#.Nil
- (#error.Success output)
+ (#try.Success output)
_
(exception.throw unconsumed-input remainder))
- (#error.Failure error)
- (#error.Failure error)))
+ (#try.Failure error)
+ (#try.Failure error)))
(def: #export (fail error)
(All [a] (-> Text (Parser a)))
(function (_ inputs)
- (#error.Failure error)))
+ (#try.Failure error)))
(def: #export any
{#.doc "Just returns the JSON input without applying any logic."}
@@ -58,7 +58,7 @@
(exception.throw empty-input [])
(#.Cons head tail)
- (#error.Success [tail head]))))
+ (#try.Success [tail head]))))
(template [<name> <type> <tag> <desc>]
[(def: #export <name>
@@ -124,10 +124,10 @@
(case head
(#/.Array values)
(case (//.run parser (row.to-list values))
- (#error.Failure error)
+ (#try.Failure error)
(fail error)
- (#error.Success [remainder output])
+ (#try.Success [remainder output])
(case remainder
#.Nil
(wrap output)
@@ -151,10 +151,10 @@
(list (#/.String key) value)))
list.concat
(//.run parser))
- (#error.Failure error)
+ (#try.Failure error)
(fail error)
- (#error.Success [remainder output])
+ (#try.Success [remainder output])
(case remainder
#.Nil
(wrap output)
@@ -173,15 +173,15 @@
(^ (list& (#/.String key) value inputs'))
(if (text@= key field-name)
(case (//.run parser (list value))
- (#error.Success [#.Nil output])
- (#error.Success [inputs' output])
+ (#try.Success [#.Nil output])
+ (#try.Success [inputs' output])
- (#error.Success [inputs'' _])
+ (#try.Success [inputs'' _])
(exception.throw unconsumed-input inputs'')
- (#error.Failure error)
- (#error.Failure error))
- (do error.monad
+ (#try.Failure error)
+ (#try.Failure error))
+ (do try.monad
[[inputs'' output] (recur inputs')]
(wrap [(list& (#/.String key) value inputs'')
output])))
diff --git a/stdlib/source/lux/control/parser/synthesis.lux b/stdlib/source/lux/control/parser/synthesis.lux
index a239b6931..784f08698 100644
--- a/stdlib/source/lux/control/parser/synthesis.lux
+++ b/stdlib/source/lux/control/parser/synthesis.lux
@@ -3,9 +3,9 @@
[abstract
[monad (#+ do)]]
[control
+ ["." try (#+ Try)]
["." exception (#+ exception:)]]
[data
- ["." error (#+ Error)]
["." bit]
["." name]
[number
@@ -41,15 +41,15 @@
(//.Parser ..Input))
(def: #export (run input parser)
- (All [a] (-> ..Input (Parser a) (Error a)))
+ (All [a] (-> ..Input (Parser a) (Try a)))
(case (parser input)
- (#error.Failure error)
- (#error.Failure error)
+ (#try.Failure error)
+ (#try.Failure error)
- (#error.Success [#.Nil value])
- (#error.Success value)
+ (#try.Success [#.Nil value])
+ (#try.Success value)
- (#error.Success [unconsumed _])
+ (#try.Success [unconsumed _])
(exception.throw ..unconsumed-input unconsumed)))
(def: #export any
@@ -60,7 +60,7 @@
(exception.throw ..empty-input [])
(#.Cons [head tail])
- (#error.Success [tail head]))))
+ (#try.Success [tail head]))))
(template [<query> <assertion> <tag> <type> <eq>]
[(def: #export <query>
@@ -68,7 +68,7 @@
(.function (_ input)
(case input
(^ (list& (<tag> x) input'))
- (#error.Success [input' x])
+ (#try.Success [input' x])
_
(exception.throw ..cannot-parse input))))
@@ -79,7 +79,7 @@
(case input
(^ (list& (<tag> actual) input'))
(if (:: <eq> = expected actual)
- (#error.Success [input' []])
+ (#try.Success [input' []])
(exception.throw ..cannot-parse input))
_
@@ -99,9 +99,9 @@
(.function (_ input)
(case input
(^ (list& (/.tuple head) tail))
- (do error.monad
+ (do try.monad
[output (..run head parser)]
- (#error.Success [tail output]))
+ (#try.Success [tail output]))
_
(exception.throw ..cannot-parse input))))
@@ -112,9 +112,9 @@
(case input
(^ (list& (/.function/abstraction [environment actual body]) tail))
(if (n/= expected actual)
- (do error.monad
+ (do try.monad
[output (..run (list body) parser)]
- (#error.Success [tail [environment output]]))
+ (#try.Success [tail [environment output]]))
(exception.throw ..wrong-arity [expected actual]))
_
diff --git a/stdlib/source/lux/control/parser/text.lux b/stdlib/source/lux/control/parser/text.lux
index 7c7c7fe4a..0e57f02f6 100644
--- a/stdlib/source/lux/control/parser/text.lux
+++ b/stdlib/source/lux/control/parser/text.lux
@@ -3,11 +3,11 @@
[abstract
[monad (#+ Monad do)]]
[control
+ ["." try (#+ Try)]
["." exception (#+ exception:)]]
[data
["." product]
["." maybe]
- ["." error (#+ Error)]
["/" text ("#@." monoid)]
[number
["." nat ("#@." decimal)]]
@@ -47,20 +47,20 @@
(exception: #export cannot-slice)
(def: #export (run parser input)
- (All [a] (-> (Parser a) Text (Error a)))
+ (All [a] (-> (Parser a) Text (Try a)))
(case (parser [start-offset input])
- (#error.Failure msg)
- (#error.Failure msg)
+ (#try.Failure msg)
+ (#try.Failure msg)
- (#error.Success [[end-offset _] output])
+ (#try.Success [[end-offset _] output])
(if (n/= end-offset (/.size input))
- (#error.Success output)
+ (#try.Success output)
(exception.throw ..unconsumed-input [end-offset input]))))
(def: #export offset
(Parser Offset)
(function (_ (^@ input [offset tape]))
- (#error.Success [input offset])))
+ (#try.Success [input offset])))
(def: (with-slices parser)
(-> (Parser (List Slice)) (Parser Slice))
@@ -80,7 +80,7 @@
(function (_ [offset tape])
(case (/.nth offset tape)
(#.Some output)
- (#error.Success [[("lux i64 +" 1 offset) tape] (/.from-code output)])
+ (#try.Success [[("lux i64 +" 1 offset) tape] (/.from-code output)])
_
(exception.throw ..cannot-parse []))))
@@ -89,9 +89,9 @@
{#.doc "Just returns the next character without applying any logic."}
(Parser Slice)
(function (_ [offset tape])
- (#error.Success [[("lux i64 +" 1 offset) tape]
- {#basis offset
- #distance 1}])))
+ (#try.Success [[("lux i64 +" 1 offset) tape]
+ {#basis offset
+ #distance 1}])))
(template [<name> <type> <any>]
[(def: #export (<name> p)
@@ -99,7 +99,7 @@
(All [a] (-> (Parser a) (Parser <type>)))
(function (_ input)
(case (p input)
- (#error.Failure msg)
+ (#try.Failure msg)
(<any> input)
_
@@ -116,12 +116,12 @@
(case (/.index-of' reference offset tape)
(#.Some where)
(if (n/= offset where)
- (#error.Success [[("lux i64 +" (/.size reference) offset) tape]
- []])
- (#error.Failure ($_ /@compose "Could not match: " (/.encode reference) " @ " (maybe.assume (/.clip' offset tape)))))
+ (#try.Success [[("lux i64 +" (/.size reference) offset) tape]
+ []])
+ (#try.Failure ($_ /@compose "Could not match: " (/.encode reference) " @ " (maybe.assume (/.clip' offset tape)))))
_
- (#error.Failure ($_ /@compose "Could not match: " (/.encode reference))))))
+ (#try.Failure ($_ /@compose "Could not match: " (/.encode reference))))))
(def: #export (this? reference)
{#.doc "Lex a text if it matches the given sample."}
@@ -129,25 +129,25 @@
(function (_ (^@ input [offset tape]))
(case (/.index-of' reference offset tape)
(^multi (#.Some where) (n/= offset where))
- (#error.Success [[("lux i64 +" (/.size reference) offset) tape]
- #1])
+ (#try.Success [[("lux i64 +" (/.size reference) offset) tape]
+ #1])
_
- (#error.Success [input #0]))))
+ (#try.Success [input #0]))))
(def: #export end
{#.doc "Ensure the parser's input is empty."}
(Parser Any)
(function (_ (^@ input [offset tape]))
(if (n/= offset (/.size tape))
- (#error.Success [input []])
+ (#try.Success [input []])
(exception.throw ..unconsumed-input input))))
(def: #export end?
{#.doc "Ask if the parser's input is empty."}
(Parser Bit)
(function (_ (^@ input [offset tape]))
- (#error.Success [input (n/= offset (/.size tape))])))
+ (#try.Success [input (n/= offset (/.size tape))])))
(def: #export peek
{#.doc "Lex the next character (without consuming it from the input)."}
@@ -155,7 +155,7 @@
(function (_ (^@ input [offset tape]))
(case (/.nth offset tape)
(#.Some output)
- (#error.Success [input (/.from-code output)])
+ (#try.Success [input (/.from-code output)])
_
(exception.throw ..cannot-parse []))))
@@ -164,7 +164,7 @@
{#.doc "Get all of the remaining input (without consuming it)."}
(Parser Text)
(function (_ (^@ input [offset tape]))
- (#error.Success [input (remaining offset tape)])))
+ (#try.Success [input (remaining offset tape)])))
(def: #export (range bottom top)
{#.doc "Only lex characters within a range."}
@@ -216,10 +216,10 @@
(#.Some output)
(let [output (/.from-code output)]
(if (<modifier> (/.contains? output options))
- (#error.Success [[("lux i64 +" 1 offset) tape] output])
- (#error.Failure ($_ /@compose "Character (" output
- ") is should " <description-modifier>
- "be one of: " options))))
+ (#try.Success [[("lux i64 +" 1 offset) tape] output])
+ (#try.Failure ($_ /@compose "Character (" output
+ ") is should " <description-modifier>
+ "be one of: " options))))
_
(exception.throw ..cannot-parse []))))]
@@ -237,12 +237,12 @@
(#.Some output)
(let [output (/.from-code output)]
(if (<modifier> (/.contains? output options))
- (#error.Success [[("lux i64 +" 1 offset) tape]
- {#basis offset
- #distance 1}])
- (#error.Failure ($_ /@compose "Character (" output
- ") is should " <description-modifier>
- "be one of: " options))))
+ (#try.Success [[("lux i64 +" 1 offset) tape]
+ {#basis offset
+ #distance 1}])
+ (#try.Failure ($_ /@compose "Character (" output
+ ") is should " <description-modifier>
+ "be one of: " options))))
_
(exception.throw ..cannot-parse []))))]
@@ -258,8 +258,8 @@
(case (/.nth offset tape)
(#.Some output)
(if (p output)
- (#error.Success [[("lux i64 +" 1 offset) tape] (/.from-code output)])
- (#error.Failure ($_ /@compose "Character does not satisfy predicate: " (/.from-code output))))
+ (#try.Success [[("lux i64 +" 1 offset) tape] (/.from-code output)])
+ (#try.Failure ($_ /@compose "Character does not satisfy predicate: " (/.from-code output))))
_
(exception.throw ..cannot-parse []))))
@@ -346,11 +346,11 @@
(All [a] (-> Text (Parser a) (Parser a)))
(function (_ real-input)
(case (run parser local-input)
- (#error.Failure error)
- (#error.Failure error)
+ (#try.Failure error)
+ (#try.Failure error)
- (#error.Success value)
- (#error.Success [real-input value]))))
+ (#try.Success value)
+ (#try.Success [real-input value]))))
(def: #export (slice parser)
(-> (Parser Slice) (Parser Text))
@@ -359,7 +359,7 @@
(function (_ (^@ input [offset tape]))
(case (/.clip basis ("lux i64 +" basis distance) tape)
(#.Some output)
- (#error.Success [input output])
+ (#try.Success [input output])
#.None
(exception.throw ..cannot-slice [])))))
diff --git a/stdlib/source/lux/control/parser/tree.lux b/stdlib/source/lux/control/parser/tree.lux
index 50c8c8a0e..3dbc5522d 100644
--- a/stdlib/source/lux/control/parser/tree.lux
+++ b/stdlib/source/lux/control/parser/tree.lux
@@ -1,9 +1,9 @@
(.module:
[lux #*
[control
+ ["." try (#+ Try)]
["." exception (#+ exception:)]]
[data
- ["." error (#+ Error)]
[tree (#+ Tree)
["." zipper (#+ Zipper)]]]]
["." //])
@@ -12,22 +12,22 @@
(//.Parser (Zipper t) a))
(def: #export (run-zipper zipper parser)
- (All [t a] (-> (Zipper t) (Parser t a) (Error a)))
+ (All [t a] (-> (Zipper t) (Parser t a) (Try a)))
(case (//.run zipper parser)
- (#error.Success [zipper output])
- (#error.Success output)
+ (#try.Success [zipper output])
+ (#try.Success output)
- (#error.Failure error)
- (#error.Failure error)))
+ (#try.Failure error)
+ (#try.Failure error)))
(def: #export (run tree parser)
- (All [t a] (-> (Tree t) (Parser t a) (Error a)))
+ (All [t a] (-> (Tree t) (Parser t a) (Try a)))
(run-zipper (zipper.zip tree) parser))
(def: #export value
(All [t] (Parser t t))
(function (_ zipper)
- (#error.Success [zipper (zipper.value zipper)])))
+ (#try.Success [zipper (zipper.value zipper)])))
(exception: #export cannot-move-further)
@@ -38,7 +38,7 @@
(let [next (<direction> zipper)]
(if (is? zipper next)
(exception.throw cannot-move-further [])
- (#error.Success [next []])))))]
+ (#try.Success [next []])))))]
[up zipper.up]
[down zipper.down]
diff --git a/stdlib/source/lux/control/parser/type.lux b/stdlib/source/lux/control/parser/type.lux
index 3fe852739..6e42cad87 100644
--- a/stdlib/source/lux/control/parser/type.lux
+++ b/stdlib/source/lux/control/parser/type.lux
@@ -3,11 +3,11 @@
[abstract
["." monad (#+ do)]]
[control
+ ["." try (#+ Try)]
["." exception (#+ exception:)]
["." function]]
[data
["." name ("#@." codec)]
- ["." error (#+ Error)]
[number
["." nat ("#@." decimal)]]
["." text ("#@." monoid)
@@ -63,67 +63,67 @@
(def: #export fresh Env (dictionary.new nat.hash))
(def: (run' env types poly)
- (All [a] (-> Env (List Type) (Parser a) (Error a)))
+ (All [a] (-> Env (List Type) (Parser a) (Try a)))
(case (//.run poly [env types])
- (#error.Failure error)
- (#error.Failure error)
+ (#try.Failure error)
+ (#try.Failure error)
- (#error.Success [[env' remaining] output])
+ (#try.Success [[env' remaining] output])
(case remaining
#.Nil
- (#error.Success output)
+ (#try.Success output)
_
(exception.throw unconsumed remaining))))
(def: #export (run type poly)
- (All [a] (-> Type (Parser a) (Error a)))
+ (All [a] (-> Type (Parser a) (Try a)))
(run' fresh (list type) poly))
(def: #export env
(Parser Env)
(.function (_ [env inputs])
- (#error.Success [[env inputs] env])))
+ (#try.Success [[env inputs] env])))
(def: (with-env temp poly)
(All [a] (-> Env (Parser a) (Parser a)))
(.function (_ [env inputs])
(case (//.run poly [temp inputs])
- (#error.Failure error)
- (#error.Failure error)
+ (#try.Failure error)
+ (#try.Failure error)
- (#error.Success [[_ remaining] output])
- (#error.Success [[env remaining] output]))))
+ (#try.Success [[_ remaining] output])
+ (#try.Success [[env remaining] output]))))
(def: #export peek
(Parser Type)
(.function (_ [env inputs])
(case inputs
#.Nil
- (#error.Failure "Empty stream of types.")
+ (#try.Failure "Empty stream of types.")
(#.Cons headT tail)
- (#error.Success [[env inputs] headT]))))
+ (#try.Success [[env inputs] headT]))))
(def: #export any
(Parser Type)
(.function (_ [env inputs])
(case inputs
#.Nil
- (#error.Failure "Empty stream of types.")
+ (#try.Failure "Empty stream of types.")
(#.Cons headT tail)
- (#error.Success [[env tail] headT]))))
+ (#try.Success [[env tail] headT]))))
(def: #export (local types poly)
(All [a] (-> (List Type) (Parser a) (Parser a)))
(.function (_ [env pass-through])
(case (run' env types poly)
- (#error.Failure error)
- (#error.Failure error)
+ (#try.Failure error)
+ (#try.Failure error)
- (#error.Success output)
- (#error.Success [[env pass-through] output]))))
+ (#try.Success output)
+ (#try.Success [[env pass-through] output]))))
(def: (label idx)
(-> Nat Code)
@@ -137,11 +137,11 @@
(case (//.run poly
[(dictionary.put current-id [type g!var] env)
inputs])
- (#error.Failure error)
- (#error.Failure error)
+ (#try.Failure error)
+ (#try.Failure error)
- (#error.Success [[_ inputs'] output])
- (#error.Success [[env inputs'] [g!var output]])))))
+ (#try.Success [[_ inputs'] output])
+ (#try.Success [[env inputs'] [g!var output]])))))
(template [<name> <flattener> <tag> <exception>]
[(def: #export (<name> poly)
diff --git a/stdlib/source/lux/control/parser/xml.lux b/stdlib/source/lux/control/parser/xml.lux
index be5c0f7b6..f9ac14f8f 100644
--- a/stdlib/source/lux/control/parser/xml.lux
+++ b/stdlib/source/lux/control/parser/xml.lux
@@ -3,9 +3,9 @@
[abstract
[monad (#+ do)]]
[control
+ ["." try (#+ Try)]
["." exception (#+ exception:)]]
[data
- ["." error (#+ Error)]
["." name ("#@." equivalence codec)]
["." text ("#@." monoid)]
[collection
@@ -43,7 +43,7 @@
(#.Cons head tail)
(case head
(#/.Text value)
- (#error.Success [tail value])
+ (#try.Success [tail value])
(#/.Node _)
(exception.throw unexpected-input [])))))
@@ -66,18 +66,18 @@
(exception.throw unknown-attribute [])
(#.Some value)
- (#error.Success [docs value]))))))
+ (#try.Success [docs value]))))))
(def: (run' reader docs)
- (All [a] (-> (Parser a) (List XML) (Error a)))
+ (All [a] (-> (Parser a) (List XML) (Try a)))
(case (//.run reader docs)
- (#error.Success [remaining output])
+ (#try.Success [remaining output])
(if (list.empty? remaining)
- (#error.Success output)
+ (#try.Success output)
(exception.throw unconsumed-inputs remaining))
- (#error.Failure error)
- (#error.Failure error)))
+ (#try.Failure error)
+ (#try.Failure error)))
(def: #export (node tag)
(-> Name (Parser Any))
@@ -93,7 +93,7 @@
(#/.Node _tag _attrs _children)
(if (name@= tag _tag)
- (#error.Success [docs []])
+ (#try.Success [docs []])
(exception.throw wrong-tag tag))))))
(def: #export (children reader)
@@ -109,7 +109,7 @@
(exception.throw unexpected-input [])
(#/.Node _tag _attrs _children)
- (do error.monad
+ (do try.monad
[output (run' reader _children)]
(wrap [tail output]))))))
@@ -121,8 +121,8 @@
(exception.throw empty-input [])
(#.Cons head tail)
- (#error.Success [tail []]))))
+ (#try.Success [tail []]))))
(def: #export (run reader document)
- (All [a] (-> (Parser a) XML (Error a)))
+ (All [a] (-> (Parser a) XML (Try a)))
(run' reader (list document)))