aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source
diff options
context:
space:
mode:
authorEduardo Julian2018-12-15 18:32:31 -0400
committerEduardo Julian2018-12-15 18:32:31 -0400
commitee0c268d2e7922ce4d1b1b11291e6858977cce74 (patch)
treee8dcd01dd4b07727f79892278d146403d56a16fe /stdlib/source
parent5f7896ac2cfa8cc9b3ca79c922438412e440a922 (diff)
Re-named the "Error" tag to "Failure".
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/cli.lux16
-rw-r--r--stdlib/source/lux/control/codec.lux10
-rw-r--r--stdlib/source/lux/control/concurrency/actor.lux2
-rw-r--r--stdlib/source/lux/control/concurrency/task.lux10
-rw-r--r--stdlib/source/lux/control/exception.lux28
-rw-r--r--stdlib/source/lux/control/parser.lux128
-rw-r--r--stdlib/source/lux/control/region.lux42
-rw-r--r--stdlib/source/lux/data/collection/tree/rose/parser.lux18
-rw-r--r--stdlib/source/lux/data/error.lux40
-rw-r--r--stdlib/source/lux/data/format/binary.lux12
-rw-r--r--stdlib/source/lux/data/format/context.lux4
-rw-r--r--stdlib/source/lux/data/format/json.lux30
-rw-r--r--stdlib/source/lux/data/format/xml.lux26
-rw-r--r--stdlib/source/lux/data/number.lux44
-rw-r--r--stdlib/source/lux/data/text/lexer.lux94
-rw-r--r--stdlib/source/lux/data/text/regex.lux36
-rw-r--r--stdlib/source/lux/io.lux6
-rw-r--r--stdlib/source/lux/macro.lux156
-rw-r--r--stdlib/source/lux/macro/poly.lux48
-rw-r--r--stdlib/source/lux/macro/syntax.lux40
-rw-r--r--stdlib/source/lux/math/modular.lux14
-rw-r--r--stdlib/source/lux/platform/compiler/default/init.lux8
-rw-r--r--stdlib/source/lux/platform/compiler/default/platform.lux12
-rw-r--r--stdlib/source/lux/platform/compiler/default/syntax.lux44
-rw-r--r--stdlib/source/lux/platform/compiler/meta/cache.lux2
-rw-r--r--stdlib/source/lux/platform/compiler/meta/io/archive.lux2
-rw-r--r--stdlib/source/lux/platform/compiler/meta/io/context.lux2
-rw-r--r--stdlib/source/lux/platform/compiler/phase/analysis.lux16
-rw-r--r--stdlib/source/lux/platform/compiler/phase/analysis/case.lux2
-rw-r--r--stdlib/source/lux/platform/compiler/phase/analysis/case/coverage.lux2
-rw-r--r--stdlib/source/lux/platform/compiler/phase/analysis/macro.lux2
-rw-r--r--stdlib/source/lux/platform/compiler/phase/analysis/scope.lux8
-rw-r--r--stdlib/source/lux/platform/compiler/phase/analysis/type.lux2
-rw-r--r--stdlib/source/lux/platform/compiler/phase/extension.lux12
-rw-r--r--stdlib/source/lux/platform/compiler/phase/extension/analysis/host.jvm.lux30
-rw-r--r--stdlib/source/lux/platform/compiler/phase/synthesis/expression.lux2
-rw-r--r--stdlib/source/lux/platform/compiler/phase/translation.lux12
-rw-r--r--stdlib/source/lux/platform/interpreter.lux6
-rw-r--r--stdlib/source/lux/platform/interpreter/type.lux4
-rw-r--r--stdlib/source/lux/time/date.lux4
-rw-r--r--stdlib/source/lux/time/instant.lux4
-rw-r--r--stdlib/source/lux/type/check.lux58
-rw-r--r--stdlib/source/lux/type/quotient.lux6
-rw-r--r--stdlib/source/lux/type/refinement.lux6
-rw-r--r--stdlib/source/lux/world/file.lux4
-rw-r--r--stdlib/source/lux/world/net/tcp.jvm.lux2
46 files changed, 538 insertions, 518 deletions
diff --git a/stdlib/source/lux/cli.lux b/stdlib/source/lux/cli.lux
index 34514b5b9..b86b2a51b 100644
--- a/stdlib/source/lux/cli.lux
+++ b/stdlib/source/lux/cli.lux
@@ -34,10 +34,10 @@
(#error.Success output)
_
- (#error.Error (format "Remaining CLI inputs: " (text.join-with " " remaining))))
+ (#error.Failure (format "Remaining CLI inputs: " (text.join-with " " remaining))))
- (#error.Error error)
- (#error.Error error)))
+ (#error.Failure error)
+ (#error.Failure error)))
(def: #export any
{#.doc "Just returns the next input without applying any logic."}
@@ -48,7 +48,7 @@
(#error.Success [inputs' arg])
_
- (#error.Error "Cannot parse empty arguments."))))
+ (#error.Failure "Cannot parse empty arguments."))))
(def: #export (parse parser)
{#.doc "Parses the next input with a parsing function."}
@@ -78,10 +78,10 @@
(#error.Success [remaining output])
(#error.Success [remaining output])
- (#error.Error error)
+ (#error.Failure error)
(case immediate
#.Nil
- (#error.Error error)
+ (#error.Failure error)
(#.Cons to-omit immediate')
(do error.Monad<Error>
@@ -95,7 +95,7 @@
(function (_ inputs)
(case inputs
#.Nil (#error.Success [inputs []])
- _ (#error.Error (format "Unknown parameters: " (text.join-with " " inputs))))))
+ _ (#error.Failure (format "Unknown parameters: " (text.join-with " " inputs))))))
(def: #export (named name value)
(All [a] (-> Text (CLI a) (CLI a)))
@@ -171,7 +171,7 @@
(#error.Success [(~ g!_) (~ g!output)])
(~ g!output)
- (#error.Error (~ g!message))
+ (#error.Failure (~ g!message))
(.error! (~ g!message))
))))
)))
diff --git a/stdlib/source/lux/control/codec.lux b/stdlib/source/lux/control/codec.lux
index 5e274e766..d2641fe38 100644
--- a/stdlib/source/lux/control/codec.lux
+++ b/stdlib/source/lux/control/codec.lux
@@ -1,14 +1,16 @@
(.module:
[lux #*
- [control monad]
- [data ["e" error]]])
+ [control
+ monad]
+ [data
+ ["." error (#+ Error)]]])
## [Signatures]
(signature: #export (Codec m a)
{#.doc "A way to move back-and-forth between a type and an alternative representation for it."}
(: (-> a m)
encode)
- (: (-> m (e.Error a))
+ (: (-> m (Error a))
decode))
## [Values]
@@ -22,6 +24,6 @@
(:: Codec<c,b> encode)))
(def: (decode cy)
- (do e.Monad<Error>
+ (do error.Monad<Error>
[by (:: Codec<c,b> decode cy)]
(:: Codec<b,a> decode by))))
diff --git a/stdlib/source/lux/control/concurrency/actor.lux b/stdlib/source/lux/control/concurrency/actor.lux
index 0af0d09f9..6f4ddf2ad 100644
--- a/stdlib/source/lux/control/concurrency/actor.lux
+++ b/stdlib/source/lux/control/concurrency/actor.lux
@@ -82,7 +82,7 @@
[[head tail] |mailbox|
?state' (handle head state self)]
(case ?state'
- (#e.Error error)
+ (#e.Failure error)
(do @
[_ (end error state)]
(exec (io.run (promise.resolve [error state (#.Cons head (obituary tail))]
diff --git a/stdlib/source/lux/control/concurrency/task.lux b/stdlib/source/lux/control/concurrency/task.lux
index c03ab7647..96bc40f0a 100644
--- a/stdlib/source/lux/control/concurrency/task.lux
+++ b/stdlib/source/lux/control/concurrency/task.lux
@@ -17,7 +17,7 @@
(def: #export (fail error)
(All [a] (-> Text (Task a)))
- (:: promise.Monad<Promise> wrap (#error.Error error)))
+ (:: promise.Monad<Promise> wrap (#error.Failure error)))
(def: #export (throw exception message)
(All [e a] (-> (Exception e) e (Task a)))
@@ -37,8 +37,8 @@
(:: promise.Functor<Promise> map
(function (_ fa')
(case fa'
- (#error.Error error)
- (#error.Error error)
+ (#error.Failure error)
+ (#error.Failure error)
(#error.Success a)
(#error.Success (f a))))
@@ -65,8 +65,8 @@
(do promise.Monad<Promise>
[mma' mma]
(case mma'
- (#error.Error error)
- (wrap (#error.Error error))
+ (#error.Failure error)
+ (wrap (#error.Failure error))
(#error.Success ma)
ma))))
diff --git a/stdlib/source/lux/control/exception.lux b/stdlib/source/lux/control/exception.lux
index ca6ab6540..c5fa9632c 100644
--- a/stdlib/source/lux/control/exception.lux
+++ b/stdlib/source/lux/control/exception.lux
@@ -40,14 +40,14 @@
(#//.Success output)
(#//.Success output)
- (#//.Error error)
+ (#//.Failure error)
(let [reference (get@ #label exception)]
(if (text.starts-with? reference error)
(#//.Success (|> error
(text.clip (text.size reference) (text.size error))
maybe.assume
then))
- (#//.Error error)))))
+ (#//.Failure error)))))
(def: #export (otherwise to-do try)
{#.doc "If no handler could be found to catch the exception, then run a function as a last-resort measure."}
@@ -57,7 +57,7 @@
(#//.Success output)
output
- (#//.Error error)
+ (#//.Failure error)
(to-do error)))
(def: #export (return value)
@@ -73,7 +73,7 @@
(def: #export (throw exception message)
{#.doc "Decorate an error message with an Exception and lift it into the error-handling context."}
(All [e] (-> (Exception e) e Error))
- (#//.Error (construct exception message)))
+ (#//.Failure (construct exception message)))
(def: #export (assert exception message test)
(All [e] (-> (Exception e) e Bit (Error Any)))
@@ -139,16 +139,16 @@
(def: #export (with-stack exception message computation)
(All [e a] (-> (Exception e) e (Error a) (Error a)))
(case computation
- (#//.Error error)
- (#//.Error (case error
- ""
- (..construct exception message)
-
- _
- ($_ "lux text concat"
- (..construct exception message)
- ..separator
- error)))
+ (#//.Failure error)
+ (#//.Failure (case error
+ ""
+ (..construct exception message)
+
+ _
+ ($_ "lux text concat"
+ (..construct exception message)
+ ..separator
+ error)))
success
success))
diff --git a/stdlib/source/lux/control/parser.lux b/stdlib/source/lux/control/parser.lux
index c40de3373..4b4ef0d34 100644
--- a/stdlib/source/lux/control/parser.lux
+++ b/stdlib/source/lux/control/parser.lux
@@ -9,22 +9,22 @@
[collection
["." list ("list/." Functor<List> Monoid<List>)]]
["." product]
- ["e" error (#+ Error)]]])
+ ["." error (#+ Error)]]])
(type: #export (Parser s a)
{#.doc "A generic parser."}
- (-> s (e.Error [s a])))
+ (-> s (Error [s a])))
## [Structures]
(structure: #export Functor<Parser> (All [s] (Functor (Parser s)))
(def: (map f ma)
(function (_ input)
(case (ma input)
- (#e.Error msg)
- (#e.Error msg)
+ (#error.Failure msg)
+ (#error.Failure msg)
- (#e.Success [input' a])
- (#e.Success [input' (f a)])))))
+ (#error.Success [input' a])
+ (#error.Success [input' (f a)])))))
(structure: #export Apply<Parser> (All [s] (Apply (Parser s)))
(def: functor Functor<Parser>)
@@ -32,31 +32,31 @@
(def: (apply ff fa)
(function (_ input)
(case (ff input)
- (#e.Success [input' f])
+ (#error.Success [input' f])
(case (fa input')
- (#e.Success [input'' a])
- (#e.Success [input'' (f a)])
+ (#error.Success [input'' a])
+ (#error.Success [input'' (f a)])
- (#e.Error msg)
- (#e.Error msg))
+ (#error.Failure msg)
+ (#error.Failure msg))
- (#e.Error msg)
- (#e.Error msg)))))
+ (#error.Failure msg)
+ (#error.Failure msg)))))
(structure: #export Monad<Parser> (All [s] (Monad (Parser s)))
(def: functor Functor<Parser>)
(def: (wrap x)
(function (_ input)
- (#e.Success [input x])))
+ (#error.Success [input x])))
(def: (join mma)
(function (_ input)
(case (mma input)
- (#e.Error msg)
- (#e.Error msg)
+ (#error.Failure msg)
+ (#error.Failure msg)
- (#e.Success [input' ma])
+ (#error.Success [input' ma])
(ma input')))))
## [Parsers]
@@ -65,8 +65,8 @@
(All [s] (-> Text Bit (Parser s Any)))
(function (_ input)
(if test
- (#e.Success [input []])
- (#e.Error message))))
+ (#error.Success [input []])
+ (#error.Failure message))))
(def: #export (maybe p)
{#.doc "Optionality combinator."}
@@ -74,12 +74,15 @@
(-> (Parser s a) (Parser s (Maybe a))))
(function (_ input)
(case (p input)
- (#e.Error _) (#e.Success [input #.None])
- (#e.Success [input' x]) (#e.Success [input' (#.Some x)]))))
+ (#error.Failure _)
+ (#error.Success [input #.None])
+
+ (#error.Success [input' x])
+ (#error.Success [input' (#.Some x)]))))
(def: #export (run input p)
(All [s a]
- (-> s (Parser s a) (e.Error [s a])))
+ (-> s (Parser s a) (Error [s a])))
(p input))
(def: #export (some p)
@@ -88,12 +91,15 @@
(-> (Parser s a) (Parser s (List a))))
(function (_ input)
(case (p input)
- (#e.Error _) (#e.Success [input (list)])
- (#e.Success [input' x]) (run input'
- (do Monad<Parser>
- [xs (some p)]
- (wrap (list& x xs)))
- ))))
+ (#error.Failure _)
+ (#error.Success [input (list)])
+
+ (#error.Success [input' x])
+ (run input'
+ (do Monad<Parser>
+ [xs (some p)]
+ (wrap (list& x xs)))
+ ))))
(def: #export (many p)
{#.doc "1-or-more combinator."}
@@ -119,11 +125,14 @@
(-> (Parser s a) (Parser s b) (Parser s (| a b))))
(function (_ tokens)
(case (p1 tokens)
- (#e.Success [tokens' x1]) (#e.Success [tokens' (0 x1)])
- (#e.Error _) (run tokens
- (do Monad<Parser>
- [x2 p2]
- (wrap (1 x2))))
+ (#error.Success [tokens' x1])
+ (#error.Success [tokens' (0 x1)])
+
+ (#error.Failure _)
+ (run tokens
+ (do Monad<Parser>
+ [x2 p2]
+ (wrap (1 x2))))
)))
(def: #export (either pl pr)
@@ -132,8 +141,11 @@
(-> (Parser s a) (Parser s a) (Parser s a)))
(function (_ tokens)
(case (pl tokens)
- (#e.Error _) (pr tokens)
- output output
+ (#error.Failure _)
+ (pr tokens)
+
+ output
+ output
)))
(def: #export (exactly n p)
@@ -160,10 +172,10 @@
(if (n/> 0 n)
(function (_ input)
(case (p input)
- (#e.Error msg)
- (#e.Success [input (list)])
+ (#error.Failure msg)
+ (#error.Success [input (list)])
- (#e.Success [input' x])
+ (#error.Success [input' x])
(run input'
(do Monad<Parser>
[xs (at-most (dec n) p)]
@@ -198,42 +210,42 @@
(All [s a] (-> (Parser s a) (Parser s Any)))
(function (_ input)
(case (p input)
- (#e.Error msg)
- (#e.Success [input []])
+ (#error.Failure msg)
+ (#error.Success [input []])
_
- (#e.Error "Expected to fail; yet succeeded."))))
+ (#error.Failure "Expected to fail; yet succeeded."))))
(def: #export (fail message)
(All [s a] (-> Text (Parser s a)))
(function (_ input)
- (#e.Error message)))
+ (#error.Failure message)))
(def: #export (lift operation)
(All [s a] (-> (Error a) (Parser s a)))
(function (_ input)
(case operation
- (#e.Success output)
- (#e.Success [input output])
+ (#error.Success output)
+ (#error.Success [input output])
- (#e.Error error)
- (#e.Error error))))
+ (#error.Failure error)
+ (#error.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)
- (#e.Error error)
- (#e.Success [input value])
+ (#error.Failure error)
+ (#error.Success [input value])
- (#e.Success [input' output])
- (#e.Success [input' output]))))
+ (#error.Success [input' output])
+ (#error.Success [input' output]))))
(def: #export remaining
(All [s] (Parser s s))
(function (_ inputs)
- (#e.Success [inputs inputs])))
+ (#error.Success [inputs inputs])))
(def: #export (rec parser)
{#.doc "Combinator for recursive parser."}
@@ -265,13 +277,13 @@
(All [s a z] (-> (Codec a z) (Parser s a) (Parser s z)))
(function (_ input)
(case (parser input)
- (#e.Error error)
- (#e.Error error)
+ (#error.Failure error)
+ (#error.Failure error)
- (#e.Success [input' to-decode])
+ (#error.Success [input' to-decode])
(case (:: Codec<a,z> decode to-decode)
- (#e.Error error)
- (#e.Error error)
+ (#error.Failure error)
+ (#error.Failure error)
- (#e.Success value)
- (#e.Success [input' value])))))
+ (#error.Success value)
+ (#error.Success [input' value])))))
diff --git a/stdlib/source/lux/control/region.lux b/stdlib/source/lux/control/region.lux
index cfd074f6b..e014777dd 100644
--- a/stdlib/source/lux/control/region.lux
+++ b/stdlib/source/lux/control/region.lux
@@ -6,7 +6,7 @@
["." monad (#+ Monad do)]
["ex" exception (#+ Exception exception:)]]
[data
- ["e" error (#+ Error)]
+ ["." error (#+ Error)]
["." text
format]
[collection
@@ -32,20 +32,20 @@
{output (Error a)})
(format error
(case output
- (#e.Success _)
+ (#error.Success _)
""
- (#e.Error error|output)
+ (#error.Failure error|output)
(format separator
error|output))))
(def: (combine-outcomes clean-up output)
(All [a] (-> (Error Any) (Error a) (Error a)))
(case clean-up
- (#e.Success _)
+ (#error.Success _)
output
- (#e.Error error|clean-up)
+ (#error.Failure error|clean-up)
(ex.throw clean-up-error [error|clean-up output])))
(def: #export (run Monad<m> computation)
@@ -64,7 +64,7 @@
(function (_ [region cleaners])
(:: Monad<m> wrap [(#.Cons (function (_ region) (cleaner value))
cleaners)
- (#e.Success value)])))
+ (#error.Success value)])))
(structure: #export (Functor<Region> Functor<m>)
(All [m]
@@ -77,11 +77,11 @@
(:: Functor<m> map
(function (_ [cleaners' temp])
[cleaners' (case temp
- (#e.Success value)
- (#e.Success (f value))
+ (#error.Success value)
+ (#error.Success (f value))
- (#e.Error error)
- (#e.Error error))])
+ (#error.Failure error)
+ (#error.Failure error))])
(fa region+cleaners))))))
(structure: #export (Apply<Region> Monad<m>)
@@ -98,12 +98,12 @@
[[cleaners ef] (ff [region cleaners])
[cleaners ea] (fa [region cleaners])]
(case [ef ea]
- [(#e.Success f) (#e.Success a)]
- (wrap [cleaners (#e.Success (f a))])
+ [(#error.Success f) (#error.Success a)]
+ (wrap [cleaners (#error.Success (f a))])
- (^or [(#e.Error error) _]
- [_ (#e.Error error)])
- (wrap [cleaners (#e.Error error)]))))))
+ (^or [(#error.Failure error) _]
+ [_ (#error.Failure error)])
+ (wrap [cleaners (#error.Failure error)]))))))
(structure: #export (Monad<Region> Monad<m>)
(All [m]
@@ -115,25 +115,25 @@
(def: (wrap value)
(function (_ [region cleaners])
- (:: Monad<m> wrap [cleaners (#e.Success value)])))
+ (:: Monad<m> wrap [cleaners (#error.Success value)])))
(def: (join ffa)
(function (_ [region cleaners])
(do Monad<m>
[[cleaners efa] (ffa [region cleaners])]
(case efa
- (#e.Success fa)
+ (#error.Success fa)
(fa [region cleaners])
- (#e.Error error)
- (wrap [cleaners (#e.Error error)]))))))
+ (#error.Failure error)
+ (wrap [cleaners (#error.Failure error)]))))))
(def: #export (fail Monad<m> error)
(All [m a]
(-> (Monad m) Text
(All [r] (Region r m a))))
(function (_ [region cleaners])
- (:: Monad<m> wrap [cleaners (#e.Error error)])))
+ (:: Monad<m> wrap [cleaners (#error.Failure error)])))
(def: #export (throw Monad<m> exception message)
(All [m e a]
@@ -149,4 +149,4 @@
(function (_ [region cleaners])
(do Monad<m>
[output operation]
- (wrap [cleaners (#e.Success output)]))))
+ (wrap [cleaners (#error.Success output)]))))
diff --git a/stdlib/source/lux/data/collection/tree/rose/parser.lux b/stdlib/source/lux/data/collection/tree/rose/parser.lux
index 5364be8c5..ba24cd908 100644
--- a/stdlib/source/lux/data/collection/tree/rose/parser.lux
+++ b/stdlib/source/lux/data/collection/tree/rose/parser.lux
@@ -4,7 +4,7 @@
["p" parser]
["ex" exception (#+ exception:)]]
[data
- ["E" error]]]
+ ["." error (#+ Error)]]]
[// (#+ Tree)
["." zipper (#+ Zipper)]])
@@ -12,22 +12,22 @@
(p.Parser (Zipper t) a))
(def: #export (run-zipper zipper parser)
- (All [t a] (-> (Zipper t) (Parser t a) (E.Error a)))
+ (All [t a] (-> (Zipper t) (Parser t a) (Error a)))
(case (p.run zipper parser)
- (#E.Success [zipper output])
- (#E.Success output)
+ (#error.Success [zipper output])
+ (#error.Success output)
- (#E.Error error)
- (#E.Error error)))
+ (#error.Failure error)
+ (#error.Failure error)))
(def: #export (run tree parser)
- (All [t a] (-> (Tree t) (Parser t a) (E.Error a)))
+ (All [t a] (-> (Tree t) (Parser t a) (Error a)))
(run-zipper (zipper.zip tree) parser))
(def: #export value
(All [t] (Parser t t))
(function (_ zipper)
- (#E.Success [zipper (zipper.value zipper)])))
+ (#error.Success [zipper (zipper.value zipper)])))
(exception: #export cannot-move-further)
@@ -38,7 +38,7 @@
(let [next (<direction> zipper)]
(if (is? zipper next)
(ex.throw cannot-move-further [])
- (#E.Success [next []])))))]
+ (#error.Success [next []])))))]
[up zipper.up]
[down zipper.down]
diff --git a/stdlib/source/lux/data/error.lux b/stdlib/source/lux/data/error.lux
index 17d88a5a0..fc30718af 100644
--- a/stdlib/source/lux/data/error.lux
+++ b/stdlib/source/lux/data/error.lux
@@ -7,15 +7,18 @@
## [Types]
(type: #export (Error a)
- (#Error Text)
+ (#Failure Text)
(#Success a))
## [Structures]
(structure: #export _ (F.Functor Error)
(def: (map f ma)
(case ma
- (#Error msg) (#Error msg)
- (#Success datum) (#Success (f datum)))))
+ (#Failure msg)
+ (#Failure msg)
+
+ (#Success datum)
+ (#Success (f datum)))))
(structure: #export _ (A.Apply Error)
(def: functor Functor<Error>)
@@ -27,11 +30,11 @@
(#Success a)
(#Success (f a))
- (#Error msg)
- (#Error msg))
+ (#Failure msg)
+ (#Failure msg))
- (#Error msg)
- (#Error msg))
+ (#Failure msg)
+ (#Failure msg))
))
(structure: #export _ (Monad Error)
@@ -42,8 +45,11 @@
(def: (join mma)
(case mma
- (#Error msg) (#Error msg)
- (#Success ma) ma)))
+ (#Failure msg)
+ (#Failure msg)
+
+ (#Success ma)
+ ma)))
(structure: #export (ErrorT Monad<M>)
(All [M] (-> (Monad M) (Monad (All [a] (M (Error a))))))
@@ -56,8 +62,8 @@
(do Monad<M>
[eMea MeMea]
(case eMea
- (#Error error)
- (wrap (#Error error))
+ (#Failure error)
+ (wrap (#Failure error))
(#Success Mea)
Mea))))
@@ -72,7 +78,7 @@
(def: #export (fail message)
(All [a] (-> Text (Error a)))
- (#Error message))
+ (#Failure message))
(def: #export (assume error)
(All [a] (-> (Error a) a))
@@ -80,24 +86,24 @@
(#Success value)
value
- (#Error message)
+ (#Failure message)
(error! message)))
(macro: #export (default tokens compiler)
{#.doc (doc "Allows you to provide a default value that will be used"
- "if a (Error x) value turns out to be #Error."
+ "if a (Error x) value turns out to be #Failure."
(is? +10
(default +20 (#Success +10)))
(is? +20
- (default +20 (#Error "KABOOM!"))))}
+ (default +20 (#Failure "KABOOM!"))))}
(case tokens
(^ (list else error))
(#Success [compiler (list (` (case (~ error)
(#..Success (~' g!temp))
(~' g!temp)
- (#..Error (~ [dummy-cursor (#.Identifier ["" ""])]))
+ (#..Failure (~ [dummy-cursor (#.Identifier ["" ""])]))
(~ else))))])
_
- (#Error "Wrong syntax for default")))
+ (#Failure "Wrong syntax for default")))
diff --git a/stdlib/source/lux/data/format/binary.lux b/stdlib/source/lux/data/format/binary.lux
index 4657b48d5..b21887854 100644
--- a/stdlib/source/lux/data/format/binary.lux
+++ b/stdlib/source/lux/data/format/binary.lux
@@ -47,8 +47,8 @@
(def: #export (read format input)
(All [a] (-> (Format a) Binary (Error a)))
(case ((get@ #read format) [0 input])
- (#error.Error msg)
- (#error.Error msg)
+ (#error.Failure msg)
+ (#error.Failure msg)
(#error.Success [[end _] output])
(let [length (binary.size input)]
@@ -70,8 +70,8 @@
(#error.Success data)
(#error.Success [(n/+ <size> offset) binary] data)
- (#error.Error error)
- (#error.Error error)))
+ (#error.Failure error)
+ (#error.Failure error)))
#write (function (_ value)
[<size>
(function (_ offset binary)
@@ -163,8 +163,8 @@
_
(ex.throw invalid-tag [2 data]))
- (#error.Error error)
- (#error.Error error)))
+ (#error.Failure error)
+ (#error.Failure error)))
#write (function (_ value)
[1
(function (_ offset binary)
diff --git a/stdlib/source/lux/data/format/context.lux b/stdlib/source/lux/data/format/context.lux
index b5d86139a..749185f85 100644
--- a/stdlib/source/lux/data/format/context.lux
+++ b/stdlib/source/lux/data/format/context.lux
@@ -36,5 +36,5 @@
(#error.Success [_ output])
(#error.Success output)
- (#error.Error error)
- (#error.Error error)))
+ (#error.Failure error)
+ (#error.Failure error)))
diff --git a/stdlib/source/lux/data/format/json.lux b/stdlib/source/lux/data/format/json.lux
index 63075804e..7d2e90270 100644
--- a/stdlib/source/lux/data/format/json.lux
+++ b/stdlib/source/lux/data/format/json.lux
@@ -102,7 +102,7 @@
(#error.Success (dictionary.keys obj))
_
- (#error.Error ($_ text/compose "Cannot get the fields of a non-object."))))
+ (#error.Failure ($_ text/compose "Cannot get the fields of a non-object."))))
(def: #export (get key json)
{#.doc "A JSON object field getter."}
@@ -114,10 +114,10 @@
(#error.Success value)
#.None
- (#error.Error ($_ text/compose "Missing field '" key "' on object.")))
+ (#error.Failure ($_ text/compose "Missing field '" key "' on object.")))
_
- (#error.Error ($_ text/compose "Cannot get field '" key "' of a non-object."))))
+ (#error.Failure ($_ text/compose "Cannot get field '" key "' of a non-object."))))
(def: #export (set key value json)
{#.doc "A JSON object field setter."}
@@ -127,7 +127,7 @@
(#error.Success (#Object (dictionary.put key value obj)))
_
- (#error.Error ($_ text/compose "Cannot set field '" key "' of a non-object."))))
+ (#error.Failure ($_ text/compose "Cannot set field '" key "' of a non-object."))))
(do-template [<name> <tag> <type> <desc>]
[(def: #export (<name> key json)
@@ -138,10 +138,10 @@
(#error.Success value)
(#error.Success _)
- (#error.Error ($_ text/compose "Wrong value type at key: " key))
+ (#error.Failure ($_ text/compose "Wrong value type at key: " key))
- (#error.Error error)
- (#error.Error error)))]
+ (#error.Failure error)
+ (#error.Failure error)))]
[get-boolean #Boolean Boolean "booleans"]
[get-number #Number Number "numbers"]
@@ -258,13 +258,13 @@
_
(ex.throw unconsumed-input remainder))
- (#error.Error error)
- (#error.Error error)))
+ (#error.Failure error)
+ (#error.Failure error)))
(def: #export (fail error)
(All [a] (-> Text (Reader a)))
(function (_ inputs)
- (#error.Error error)))
+ (#error.Failure error)))
(def: #export any
{#.doc "Just returns the JSON input without applying any logic."}
@@ -342,7 +342,7 @@
(case head
(#Array values)
(case (p.run (row.to-list values) parser)
- (#error.Error error)
+ (#error.Failure error)
(fail error)
(#error.Success [remainder output])
@@ -369,7 +369,7 @@
(list (#String key) value)))
list.concat)
parser)
- (#error.Error error)
+ (#error.Failure error)
(fail error)
(#error.Success [remainder output])
@@ -397,8 +397,8 @@
(#error.Success [inputs'' _])
(ex.throw unconsumed-input inputs'')
- (#error.Error error)
- (#error.Error error))
+ (#error.Failure error)
+ (#error.Failure error))
(do error.Monad<Error>
[[inputs'' output] (recur inputs')]
(wrap [(list& (#String key) value inputs'')
@@ -459,7 +459,7 @@
offset (l.many l.decimal)]
(wrap ($_ text/compose mark (if signed?' "-" "") offset))))]
(case (frac/decode ($_ text/compose (if signed? "-" "") digits "." decimals exp))
- (#error.Error message)
+ (#error.Failure message)
(p.fail message)
(#error.Success value)
diff --git a/stdlib/source/lux/data/format/xml.lux b/stdlib/source/lux/data/format/xml.lux
index 0ed744b46..e1cbda0db 100644
--- a/stdlib/source/lux/data/format/xml.lux
+++ b/stdlib/source/lux/data/format/xml.lux
@@ -8,7 +8,7 @@
["ex" exception (#+ exception:)]]
[data
["." number]
- ["E" error]
+ ["." error (#+ Error)]
["." product]
["." name ("name/." Equivalence<Name> Codec<Text,Name>)]
["." text ("text/." Equivalence<Text> Monoid<Text>)
@@ -171,7 +171,7 @@
(p.after (p.maybe xml-header^))))
(def: #export (read input)
- (-> Text (E.Error XML))
+ (-> Text (Error XML))
(l.run input xml^))
(def: (sanitize-value input)
@@ -271,7 +271,7 @@
(#.Cons head tail)
(case head
(#Text value)
- (#E.Success [tail value])
+ (#error.Success [tail value])
(#Node _)
(ex.throw unexpected-input [])))))
@@ -294,18 +294,18 @@
(ex.throw unknown-attribute [])
(#.Some value)
- (#E.Success [docs value]))))))
+ (#error.Success [docs value]))))))
(def: (run' docs reader)
- (All [a] (-> (List XML) (Reader a) (E.Error a)))
+ (All [a] (-> (List XML) (Reader a) (Error a)))
(case (p.run docs reader)
- (#E.Success [remaining output])
+ (#error.Success [remaining output])
(if (list.empty? remaining)
- (#E.Success output)
+ (#error.Success output)
(ex.throw unconsumed-inputs remaining))
- (#E.Error error)
- (#E.Error error)))
+ (#error.Failure error)
+ (#error.Failure error)))
(def: #export (node tag)
(-> Name (Reader Any))
@@ -321,7 +321,7 @@
(#Node _tag _attrs _children)
(if (name/= tag _tag)
- (#E.Success [docs []])
+ (#error.Success [docs []])
(ex.throw wrong-tag tag))))))
(def: #export (children reader)
@@ -337,7 +337,7 @@
(ex.throw unexpected-input [])
(#Node _tag _attrs _children)
- (do E.Monad<Error>
+ (do error.Monad<Error>
[output (run' _children reader)]
(wrap [tail output]))))))
@@ -349,8 +349,8 @@
(ex.throw empty-input [])
(#.Cons head tail)
- (#E.Success [tail []]))))
+ (#error.Success [tail []]))))
(def: #export (run document reader)
- (All [a] (-> XML (Reader a) (E.Error a)))
+ (All [a] (-> XML (Reader a) (Error a)))
(run' (list document) reader))
diff --git a/stdlib/source/lux/data/number.lux b/stdlib/source/lux/data/number.lux
index efd965d1b..b133e905f 100644
--- a/stdlib/source/lux/data/number.lux
+++ b/stdlib/source/lux/data/number.lux
@@ -172,7 +172,7 @@
(#error.Success value)
#.None
- (#error.Error <error>))))]
+ (#error.Failure <error>))))]
[Frac "lux frac encode" "lux frac decode" "Could not decode Frac"]
)
@@ -316,13 +316,13 @@
(if (n/< input-size idx)
(case (<to-value> (get-char! repr idx))
#.None
- (#error.Error ("lux text concat" <error> repr))
+ (#error.Failure ("lux text concat" <error> repr))
(#.Some digit-value)
(recur (inc idx)
(|> output (n/* <base>) (n/+ digit-value))))
(#error.Success output)))
- (#error.Error ("lux text concat" <error> repr))))))]
+ (#error.Failure ("lux text concat" <error> repr))))))]
[Binary@Codec<Text,Nat> 2 binary-character binary-value "Invalid binary syntax for Nat: "]
[Octal@Codec<Text,Nat> 8 octal-character octal-value "Invalid octal syntax for Nat: "]
@@ -355,7 +355,7 @@
(if (n/< input-size idx)
(case (<to-value> (get-char! repr idx))
#.None
- (#error.Error <error>)
+ (#error.Failure <error>)
(#.Some digit-value)
(recur (inc idx)
@@ -385,8 +385,8 @@
(int-decode-loop input-size repr sign <base> <to-value> <error>)
#.None
- (#error.Error <error>))
- (#error.Error <error>)))))]
+ (#error.Failure <error>))
+ (#error.Failure <error>)))))]
[Binary@Codec<Text,Int> +2 binary-character binary-value "Invalid binary syntax for Int: "]
[Octal@Codec<Text,Int> +8 octal-character octal-value "Invalid octal syntax for Int: "]
@@ -399,7 +399,7 @@
("lux text clip" input 1 ("lux text size" input)))
(do-template [<struct> <nat> <char-bit-size> <error>]
- [(with-expansions [<error-output> (as-is (#error.Error ("lux text concat" <error> repr)))]
+ [(with-expansions [<error-output> (as-is (#error.Failure ("lux text concat" <error> repr)))]
(structure: #export <struct> (Codec Text Rev)
(def: (encode value)
(let [raw-output (de-prefix (:: <nat> encode (:coerce Nat value)))
@@ -476,16 +476,16 @@
(#error.Success dec-rev)
dec-rev
- (#error.Error error)
+ (#error.Failure error)
(error! error))]
(#error.Success (f/+ (int-to-frac whole)
(f/* sign adjusted-decimal))))
_
- (#error.Error ("lux text concat" <error> repr))))
+ (#error.Failure ("lux text concat" <error> repr))))
_
- (#error.Error ("lux text concat" <error> repr)))))]
+ (#error.Failure ("lux text concat" <error> repr)))))]
[Binary@Codec<Text,Frac> Binary@Codec<Text,Int> +2.0 "01" "Invalid binary syntax: "]
)
@@ -656,14 +656,14 @@
("lux text concat" (<to> whole-part))
("lux text concat" (if (f/= -1.0 sign) "-" "+")))]
(case (:: Binary@Codec<Text,Frac> decode as-binary)
- (#error.Error _)
- (#error.Error ("lux text concat" <error> repr))
+ (#error.Failure _)
+ (#error.Failure ("lux text concat" <error> repr))
output
output))
_
- (#error.Error ("lux text concat" <error> repr))))))]
+ (#error.Failure ("lux text concat" <error> repr))))))]
[Octal@Codec<Text,Frac> "Invalid octaladecimal syntax: " binary-to-octal octal-to-binary]
[Hex@Codec<Text,Frac> "Invalid hexadecimal syntax: " binary-to-hex hex-to-binary]
@@ -683,7 +683,7 @@
(~ example-2))))]))
_
- (#error.Error "Wrong syntax for 'encoding-doc'.")))
+ (#error.Failure "Wrong syntax for 'encoding-doc'.")))
(def: (underscore-prefixed? number)
(-> Text Bit)
@@ -704,29 +704,29 @@
(case tokens
(#.Cons [meta (#.Text repr')] #.Nil)
(if (underscore-prefixed? repr')
- (#error.Error <error>)
+ (#error.Failure <error>)
(let [repr (clean-underscores repr')]
(case (:: <nat> decode repr)
(#error.Success value)
(#error.Success [state (list [meta (#.Nat value)])])
- (^multi (#error.Error _)
+ (^multi (#error.Failure _)
[(:: <int> decode repr) (#error.Success value)])
(#error.Success [state (list [meta (#.Int value)])])
- (^multi (#error.Error _)
+ (^multi (#error.Failure _)
[(:: <rev> decode repr) (#error.Success value)])
(#error.Success [state (list [meta (#.Rev value)])])
- (^multi (#error.Error _)
+ (^multi (#error.Failure _)
[(:: <frac> decode repr) (#error.Success value)])
(#error.Success [state (list [meta (#.Frac value)])])
_
- (#error.Error <error>))))
+ (#error.Failure <error>))))
_
- (#error.Error <error>)))]
+ (#error.Failure <error>)))]
[bin Binary@Codec<Text,Nat> Binary@Codec<Text,Int> Binary@Codec<Text,Rev> Binary@Codec<Text,Frac>
"Invalid binary syntax."
@@ -918,8 +918,8 @@
(#error.Success (:coerce Rev output))))
#.None
- (#error.Error ("lux text concat" "Wrong syntax for Rev: " input)))
- (#error.Error ("lux text concat" "Wrong syntax for Rev: " input))))
+ (#error.Failure ("lux text concat" "Wrong syntax for Rev: " input)))
+ (#error.Failure ("lux text concat" "Wrong syntax for Rev: " input))))
))
(def: (log2 input)
diff --git a/stdlib/source/lux/data/text/lexer.lux b/stdlib/source/lux/data/text/lexer.lux
index 45a88bdf3..9ecbb99c7 100644
--- a/stdlib/source/lux/data/text/lexer.lux
+++ b/stdlib/source/lux/data/text/lexer.lux
@@ -7,7 +7,7 @@
[data
["." product]
["." maybe]
- ["e" error]
+ ["." error (#+ Error)]
[number ("nat/." Codec<Text,Nat>)]
[collection
["." list ("list/." Fold<List>)]]]
@@ -38,20 +38,20 @@
["Remaining input" (remaining offset tape)]))
(def: #export (run input lexer)
- (All [a] (-> Text (Lexer a) (e.Error a)))
+ (All [a] (-> Text (Lexer a) (Error a)))
(case (lexer [start-offset input])
- (#e.Error msg)
- (#e.Error msg)
+ (#error.Failure msg)
+ (#error.Failure msg)
- (#e.Success [[end-offset _] output])
+ (#error.Success [[end-offset _] output])
(if (n/= end-offset (//.size input))
- (#e.Success output)
+ (#error.Success output)
(ex.throw unconsumed-input [end-offset input]))))
(def: #export offset
(Lexer Offset)
(function (_ (^@ input [offset tape]))
- (#e.Success [input offset])))
+ (#error.Success [input offset])))
(def: (with-slices lexer)
(-> (Lexer (List Slice)) (Lexer Slice))
@@ -71,18 +71,18 @@
(function (_ [offset tape])
(case (//.nth offset tape)
(#.Some output)
- (#e.Success [[("lux i64 +" 1 offset) tape] (//.from-code output)])
+ (#error.Success [[("lux i64 +" 1 offset) tape] (//.from-code output)])
_
- (#e.Error cannot-lex-error))))
+ (#error.Failure cannot-lex-error))))
(def: #export any!
{#.doc "Just returns the next character without applying any logic."}
(Lexer Slice)
(function (_ [offset tape])
- (#e.Success [[("lux i64 +" 1 offset) tape]
- {#basis offset
- #distance 1}])))
+ (#error.Success [[("lux i64 +" 1 offset) tape]
+ {#basis offset
+ #distance 1}])))
(do-template [<name> <type> <any>]
[(def: #export (<name> p)
@@ -90,11 +90,11 @@
(All [a] (-> (Lexer a) (Lexer <type>)))
(function (_ input)
(case (p input)
- (#e.Error msg)
+ (#error.Failure msg)
(<any> input)
_
- (#e.Error "Expected to fail; yet succeeded."))))]
+ (#error.Failure "Expected to fail; yet succeeded."))))]
[not Text ..any]
[not! Slice ..any!]
@@ -107,12 +107,12 @@
(case (//.index-of' reference offset tape)
(#.Some where)
(if (n/= offset where)
- (#e.Success [[("lux i64 +" (//.size reference) offset) tape]
- []])
- (#e.Error ($_ text/compose "Could not match: " (//.encode reference) " @ " (maybe.assume (//.clip' offset tape)))))
+ (#error.Success [[("lux i64 +" (//.size reference) offset) tape]
+ []])
+ (#error.Failure ($_ text/compose "Could not match: " (//.encode reference) " @ " (maybe.assume (//.clip' offset tape)))))
_
- (#e.Error ($_ text/compose "Could not match: " (//.encode reference))))))
+ (#error.Failure ($_ text/compose "Could not match: " (//.encode reference))))))
(def: #export (this? reference)
{#.doc "Lex a text if it matches the given sample."}
@@ -120,25 +120,25 @@
(function (_ (^@ input [offset tape]))
(case (//.index-of' reference offset tape)
(^multi (#.Some where) (n/= offset where))
- (#e.Success [[("lux i64 +" (//.size reference) offset) tape]
- #1])
+ (#error.Success [[("lux i64 +" (//.size reference) offset) tape]
+ #1])
_
- (#e.Success [input #0]))))
+ (#error.Success [input #0]))))
(def: #export end
{#.doc "Ensure the lexer's input is empty."}
(Lexer Any)
(function (_ (^@ input [offset tape]))
(if (n/= offset (//.size tape))
- (#e.Success [input []])
+ (#error.Success [input []])
(ex.throw unconsumed-input [offset tape]))))
(def: #export end?
{#.doc "Ask if the lexer's input is empty."}
(Lexer Bit)
(function (_ (^@ input [offset tape]))
- (#e.Success [input (n/= offset (//.size tape))])))
+ (#error.Success [input (n/= offset (//.size tape))])))
(def: #export peek
{#.doc "Lex the next character (without consuming it from the input)."}
@@ -146,16 +146,16 @@
(function (_ (^@ input [offset tape]))
(case (//.nth offset tape)
(#.Some output)
- (#e.Success [input (//.from-code output)])
+ (#error.Success [input (//.from-code output)])
_
- (#e.Error cannot-lex-error))))
+ (#error.Failure cannot-lex-error))))
(def: #export get-input
{#.doc "Get all of the remaining input (without consuming it)."}
(Lexer Text)
(function (_ (^@ input [offset tape]))
- (#e.Success [input (remaining offset tape)])))
+ (#error.Success [input (remaining offset tape)])))
(def: #export (range bottom top)
{#.doc "Only lex characters within a range."}
@@ -207,13 +207,13 @@
(#.Some output)
(let [output (//.from-code output)]
(if (<modifier> (//.contains? output options))
- (#e.Success [[("lux i64 +" 1 offset) tape] output])
- (#e.Error ($_ text/compose "Character (" output
- ") is should " <description-modifier>
- "be one of: " options))))
+ (#error.Success [[("lux i64 +" 1 offset) tape] output])
+ (#error.Failure ($_ text/compose "Character (" output
+ ") is should " <description-modifier>
+ "be one of: " options))))
_
- (#e.Error cannot-lex-error))))]
+ (#error.Failure cannot-lex-error))))]
[one-of "" |>]
[none-of " not" .not]
@@ -228,15 +228,15 @@
(#.Some output)
(let [output (//.from-code output)]
(if (<modifier> (//.contains? output options))
- (#e.Success [[("lux i64 +" 1 offset) tape]
- {#basis offset
- #distance 1}])
- (#e.Error ($_ text/compose "Character (" output
- ") is should " <description-modifier>
- "be one of: " options))))
+ (#error.Success [[("lux i64 +" 1 offset) tape]
+ {#basis offset
+ #distance 1}])
+ (#error.Failure ($_ text/compose "Character (" output
+ ") is should " <description-modifier>
+ "be one of: " options))))
_
- (#e.Error cannot-lex-error))))]
+ (#error.Failure cannot-lex-error))))]
[one-of! "" |>]
[none-of! " not" .not]
@@ -249,11 +249,11 @@
(case (//.nth offset tape)
(#.Some output)
(if (p output)
- (#e.Success [[("lux i64 +" 1 offset) tape] (//.from-code output)])
- (#e.Error ($_ text/compose "Character does not satisfy predicate: " (//.from-code output))))
+ (#error.Success [[("lux i64 +" 1 offset) tape] (//.from-code output)])
+ (#error.Failure ($_ text/compose "Character does not satisfy predicate: " (//.from-code output))))
_
- (#e.Error cannot-lex-error))))
+ (#error.Failure cannot-lex-error))))
(def: #export space
{#.doc "Only lex white-space."}
@@ -337,11 +337,11 @@
(All [a] (-> Text (Lexer a) (Lexer a)))
(function (_ real-input)
(case (run local-input lexer)
- (#e.Error error)
- (#e.Error error)
+ (#error.Failure error)
+ (#error.Failure error)
- (#e.Success value)
- (#e.Success [real-input value]))))
+ (#error.Success value)
+ (#error.Success [real-input value]))))
(def: #export (slice lexer)
(-> (Lexer Slice) (Lexer Text))
@@ -350,7 +350,7 @@
(function (_ (^@ input [offset tape]))
(case (//.clip basis ("lux i64 +" basis distance) tape)
(#.Some output)
- (#e.Success [input output])
+ (#error.Success [input output])
#.None
- (#e.Error "Cannot slice.")))))
+ (#error.Failure "Cannot slice.")))))
diff --git a/stdlib/source/lux/data/text/regex.lux b/stdlib/source/lux/data/text/regex.lux
index ba0128b7b..22aa4c87c 100644
--- a/stdlib/source/lux/data/text/regex.lux
+++ b/stdlib/source/lux/data/text/regex.lux
@@ -5,7 +5,7 @@
["p" parser ("parser/." Monad<Parser>)]]
[data
["." product]
- ["e" error]
+ ["." error]
["." maybe]
["." number (#+ hex) ("int/." Codec<Text,Int>)]
[collection
@@ -319,31 +319,31 @@
(All [l r] (-> (l.Lexer [Text l]) (l.Lexer [Text r]) (l.Lexer [Text (| l r)])))
(function (_ input)
(case (left input)
- (#e.Success [input' [lt lv]])
- (#e.Success [input' [lt (0 lv)]])
+ (#error.Success [input' [lt lv]])
+ (#error.Success [input' [lt (0 lv)]])
- (#e.Error _)
+ (#error.Failure _)
(case (right input)
- (#e.Success [input' [rt rv]])
- (#e.Success [input' [rt (1 rv)]])
+ (#error.Success [input' [rt rv]])
+ (#error.Success [input' [rt (1 rv)]])
- (#e.Error error)
- (#e.Error error)))))
+ (#error.Failure error)
+ (#error.Failure error)))))
(def: (|||_^ left right)
(All [l r] (-> (l.Lexer [Text l]) (l.Lexer [Text r]) (l.Lexer Text)))
(function (_ input)
(case (left input)
- (#e.Success [input' [lt lv]])
- (#e.Success [input' lt])
+ (#error.Success [input' [lt lv]])
+ (#error.Success [input' lt])
- (#e.Error _)
+ (#error.Failure _)
(case (right input)
- (#e.Success [input' [rt rv]])
- (#e.Success [input' rt])
+ (#error.Success [input' [rt rv]])
+ (#error.Success [input' rt])
- (#e.Error error)
- (#e.Error error)))))
+ (#error.Failure error)
+ (#error.Failure error)))))
(def: (prep-alternative [num-captures alt])
(-> [Nat Code] Code)
@@ -464,11 +464,11 @@
(case (|> (regex^ current-module)
(p.before l.end)
(l.run pattern))
- (#e.Error error)
+ (#error.Failure error)
(macro.fail (format "Error while parsing regular-expression:" //.new-line
error))
- (#e.Success regex)
+ (#error.Success regex)
(wrap (list regex))
)))
@@ -489,6 +489,6 @@
(with-gensyms [g!temp]
(wrap (list& (` (^multi (~ g!temp)
[((~! l.run) (~ g!temp) (regex (~ (code.text pattern))))
- (#e.Success (~ (maybe.default g!temp bindings)))]))
+ (#error.Success (~ (maybe.default g!temp bindings)))]))
body
branches))))
diff --git a/stdlib/source/lux/io.lux b/stdlib/source/lux/io.lux
index c054c5347..92ae11066 100644
--- a/stdlib/source/lux/io.lux
+++ b/stdlib/source/lux/io.lux
@@ -79,8 +79,8 @@
(#error.Success ma)
ma
- (#error.Error error)
- (io (#error.Error error)))))
+ (#error.Failure error)
+ (io (#error.Failure error)))))
(def: #export from-io
(All [a] (-> (IO a) (Process a)))
@@ -88,7 +88,7 @@
(def: #export (fail error)
(All [a] (-> Text (Process a)))
- (io (#error.Error error)))
+ (io (#error.Failure error)))
(def: #export (throw exception message)
(All [e a] (-> (Exception e) e (Process a)))
diff --git a/stdlib/source/lux/macro.lux b/stdlib/source/lux/macro.lux
index 5d5c8f0cf..ead5b366e 100644
--- a/stdlib/source/lux/macro.lux
+++ b/stdlib/source/lux/macro.lux
@@ -8,7 +8,7 @@
["." product]
[name ("name/." Codec<Text,Name> Equivalence<Name>)]
["." maybe]
- ["e" error]
+ ["." error (#+ Error)]
["." number ("nat/." Codec<Text,Nat>)]
["." text ("text/." Monoid<Text> Equivalence<Text>)]
[collection
@@ -17,17 +17,17 @@
["." code]])
## (type: (Meta a)
-## (-> Lux (e.Error [Lux a])))
+## (-> Lux (Error [Lux a])))
(structure: #export _ (Functor Meta)
(def: (map f fa)
(function (_ compiler)
(case (fa compiler)
- (#e.Error msg)
- (#e.Error msg)
+ (#error.Failure msg)
+ (#error.Failure msg)
- (#e.Success [compiler' a])
- (#e.Success [compiler' (f a)])))))
+ (#error.Success [compiler' a])
+ (#error.Success [compiler' (f a)])))))
(structure: #export _ (Apply Meta)
(def: functor Functor<Meta>)
@@ -35,31 +35,31 @@
(def: (apply ff fa)
(function (_ compiler)
(case (ff compiler)
- (#e.Success [compiler' f])
+ (#error.Success [compiler' f])
(case (fa compiler')
- (#e.Success [compiler'' a])
- (#e.Success [compiler'' (f a)])
+ (#error.Success [compiler'' a])
+ (#error.Success [compiler'' (f a)])
- (#e.Error msg)
- (#e.Error msg))
+ (#error.Failure msg)
+ (#error.Failure msg))
- (#e.Error msg)
- (#e.Error msg)))))
+ (#error.Failure msg)
+ (#error.Failure msg)))))
(structure: #export _ (Monad Meta)
(def: functor Functor<Meta>)
(def: (wrap x)
(function (_ compiler)
- (#e.Success [compiler x])))
+ (#error.Success [compiler x])))
(def: (join mma)
(function (_ compiler)
(case (mma compiler)
- (#e.Error msg)
- (#e.Error msg)
+ (#error.Failure msg)
+ (#error.Failure msg)
- (#e.Success [compiler' ma])
+ (#error.Success [compiler' ma])
(ma compiler')))))
(def: (get k plist)
@@ -75,63 +75,63 @@
(get k plist'))))
(def: #export (run' compiler action)
- (All [a] (-> Lux (Meta a) (e.Error [Lux a])))
+ (All [a] (-> Lux (Meta a) (Error [Lux a])))
(action compiler))
(def: #export (run compiler action)
- (All [a] (-> Lux (Meta a) (e.Error a)))
+ (All [a] (-> Lux (Meta a) (Error a)))
(case (action compiler)
- (#e.Error error)
- (#e.Error error)
+ (#error.Failure error)
+ (#error.Failure error)
- (#e.Success [_ output])
- (#e.Success output)))
+ (#error.Success [_ output])
+ (#error.Success output)))
(def: #export (either left right)
{#.doc "Pick whichever computation succeeds."}
(All [a] (-> (Meta a) (Meta a) (Meta a)))
(function (_ compiler)
(case (left compiler)
- (#e.Error error)
+ (#error.Failure error)
(right compiler)
- (#e.Success [compiler' output])
- (#e.Success [compiler' output]))))
+ (#error.Success [compiler' output])
+ (#error.Success [compiler' output]))))
(def: #export (assert message test)
{#.doc "Fails with the given message if the test is #0."}
(-> Text Bit (Meta Any))
(function (_ compiler)
(if test
- (#e.Success [compiler []])
- (#e.Error message))))
+ (#error.Success [compiler []])
+ (#error.Failure message))))
(def: #export (fail msg)
{#.doc "Fails with the given message."}
(All [a]
(-> Text (Meta a)))
(function (_ _)
- (#e.Error msg)))
+ (#error.Failure msg)))
(def: #export (find-module name)
(-> Text (Meta Module))
(function (_ compiler)
(case (get name (get@ #.modules compiler))
(#.Some module)
- (#e.Success [compiler module])
+ (#error.Success [compiler module])
_
- (#e.Error ($_ text/compose "Unknown module: " name)))))
+ (#error.Failure ($_ text/compose "Unknown module: " name)))))
(def: #export current-module-name
(Meta Text)
(function (_ compiler)
(case (get@ #.current-module compiler)
(#.Some current-module)
- (#e.Success [compiler current-module])
+ (#error.Success [compiler current-module])
_
- (#e.Error "No current module.")
+ (#error.Failure "No current module.")
)))
(def: #export current-module
@@ -283,7 +283,7 @@
this-module current-module-name]
(: (Meta (Maybe Macro))
(function (_ compiler)
- (#e.Success [compiler (find-macro' (get@ #.modules compiler) this-module module name)])))))
+ (#error.Success [compiler (find-macro' (get@ #.modules compiler) this-module module name)])))))
(def: #export (expand-once syntax)
{#.doc (doc "Given code that requires applying a macro, does it once and returns the result."
@@ -360,20 +360,20 @@
(def: #export count
(Meta Nat)
(function (_ compiler)
- (#e.Success [(update@ #.seed inc compiler)
- (get@ #.seed compiler)])))
+ (#error.Success [(update@ #.seed inc compiler)
+ (get@ #.seed compiler)])))
(def: #export (gensym prefix)
{#.doc (doc "Generates a unique name as an Code node (ready to be used in code templates)."
"A prefix can be given (or just be empty text) to better identify the code for debugging purposes.")}
(-> Text (Meta Code))
(function (_ compiler)
- (#e.Success [(update@ #.seed inc compiler)
- (|> compiler
- (get@ #.seed)
- (:: number.Codec<Text,Nat> encode)
- ($_ text/compose "__gensym__" prefix)
- [""] code.identifier)])))
+ (#error.Success [(update@ #.seed inc compiler)
+ (|> compiler
+ (get@ #.seed)
+ (:: number.Codec<Text,Nat> encode)
+ ($_ text/compose "__gensym__" prefix)
+ [""] code.identifier)])))
(def: (get-local-identifier ast)
(-> Code (Meta Text))
@@ -423,12 +423,12 @@
(def: #export (module-exists? module)
(-> Text (Meta Bit))
(function (_ compiler)
- (#e.Success [compiler (case (get module (get@ #.modules compiler))
- (#.Some _)
- #1
-
- #.None
- #0)])))
+ (#error.Success [compiler (case (get module (get@ #.modules compiler))
+ (#.Some _)
+ #1
+
+ #.None
+ #0)])))
(def: (try-both f x1 x2)
(All [a b]
@@ -457,10 +457,10 @@
(get@ [#.type-context #.var-bindings])
(find-type-var var))
(^or #.None (#.Some (#.Var _)))
- (#e.Success [compiler type])
+ (#error.Success [compiler type])
(#.Some type')
- (#e.Success [compiler type'])))
+ (#error.Success [compiler type'])))
_
(:: Monad<Meta> wrap type)))
@@ -488,7 +488,7 @@
((clean-type var-type) compiler)
#.None
- (#e.Error ($_ text/compose "Unknown variable: " name))))))
+ (#error.Failure ($_ text/compose "Unknown variable: " name))))))
(def: #export (find-def name)
{#.doc "Looks-up a definition's whole data in the available modules (including the current one)."}
@@ -502,22 +502,22 @@
(^slots [#.definitions]) (get v-prefix (get@ #.modules compiler))]
(get v-name definitions)))
(#.Some definition)
- (#e.Success [compiler definition])
+ (#error.Success [compiler definition])
_
(let [current-module (|> compiler (get@ #.current-module) (maybe.default "???"))]
- (#e.Error ($_ text/compose
- "Unknown definition: " (name/encode name) text.new-line
- " Current module: " current-module text.new-line
- (case (get current-module (get@ #.modules compiler))
- (#.Some this-module)
- ($_ text/compose
- " Imports: " (|> this-module (get@ #.imports) (text.join-with ", ")) text.new-line
- " Aliases: " (|> this-module (get@ #.module-aliases) (list/map (function (_ [alias real]) ($_ text/compose alias " => " real))) (text.join-with ", ")) text.new-line)
-
- _
- "")
- " All Known modules: " (|> compiler (get@ #.modules) (list/map product.left) (text.join-with ", ")) text.new-line)))))))
+ (#error.Failure ($_ text/compose
+ "Unknown definition: " (name/encode name) text.new-line
+ " Current module: " current-module text.new-line
+ (case (get current-module (get@ #.modules compiler))
+ (#.Some this-module)
+ ($_ text/compose
+ " Imports: " (|> this-module (get@ #.imports) (text.join-with ", ")) text.new-line
+ " Aliases: " (|> this-module (get@ #.module-aliases) (list/map (function (_ [alias real]) ($_ text/compose alias " => " real))) (text.join-with ", ")) text.new-line)
+
+ _
+ "")
+ " All Known modules: " (|> compiler (get@ #.modules) (list/map product.left) (text.join-with ", ")) text.new-line)))))))
(def: #export (find-def-type name)
{#.doc "Looks-up a definition's type in the available modules (including the current one)."}
@@ -551,8 +551,8 @@
(-> Text (Meta (List [Text Definition])))
(function (_ compiler)
(case (get module-name (get@ #.modules compiler))
- #.None (#e.Error ($_ text/compose "Unknown module: " module-name))
- (#.Some module) (#e.Success [compiler (get@ #.definitions module)])
+ #.None (#error.Failure ($_ text/compose "Unknown module: " module-name))
+ (#.Some module) (#error.Success [compiler (get@ #.definitions module)])
)))
(def: #export (exports module-name)
@@ -571,7 +571,7 @@
(|> compiler
(get@ #.modules)
[compiler]
- #e.Success)))
+ #error.Success)))
(def: #export (tags-of type-name)
{#.doc "All the tags associated with a type definition."}
@@ -590,7 +590,7 @@
{#.doc "The cursor of the current expression being analyzed."}
(Meta Cursor)
(function (_ compiler)
- (#e.Success [compiler (get@ #.cursor compiler)])))
+ (#error.Success [compiler (get@ #.cursor compiler)])))
(def: #export expected-type
{#.doc "The expected type of the current expression being analyzed."}
@@ -598,10 +598,10 @@
(function (_ compiler)
(case (get@ #.expected compiler)
(#.Some type)
- (#e.Success [compiler type])
+ (#error.Success [compiler type])
#.None
- (#e.Error "Not expecting any type."))))
+ (#error.Failure "Not expecting any type."))))
(def: #export (imported-modules module-name)
{#.doc "All the modules imported by a specified module."}
@@ -660,14 +660,14 @@
(function (_ compiler)
(case (list.inits (get@ #.scopes compiler))
#.None
- (#e.Error "No local environment")
+ (#error.Failure "No local environment")
(#.Some scopes)
- (#e.Success [compiler
- (list/map (|>> (get@ [#.locals #.mappings])
- (list/map (function (_ [name [type _]])
- [name type])))
- scopes)]))))
+ (#error.Success [compiler
+ (list/map (|>> (get@ [#.locals #.mappings])
+ (list/map (function (_ [name [type _]])
+ [name type])))
+ scopes)]))))
(def: #export (un-alias def-name)
{#.doc "Given an aliased definition's name, returns the original definition being referenced."}
@@ -685,12 +685,12 @@
{#.doc "Obtains the current state of the compiler."}
(Meta Lux)
(function (_ compiler)
- (#e.Success [compiler compiler])))
+ (#error.Success [compiler compiler])))
(def: #export type-context
(Meta Type-Context)
(function (_ compiler)
- (#e.Success [compiler (get@ #.type-context compiler)])))
+ (#error.Success [compiler (get@ #.type-context compiler)])))
(do-template [<macro> <func> <desc>]
[(macro: #export (<macro> tokens)
diff --git a/stdlib/source/lux/macro/poly.lux b/stdlib/source/lux/macro/poly.lux
index 51f7a4885..be33751cc 100644
--- a/stdlib/source/lux/macro/poly.lux
+++ b/stdlib/source/lux/macro/poly.lux
@@ -11,7 +11,7 @@
["." bit]
["." maybe]
[name ("name/." Codec<Text,Name>)]
- ["e" error]
+ ["." error (#+ Error)]
["." number (#+ hex) ("nat/." Codec<Text,Nat>)]
["." text ("text/." Monoid<Text>)
format]
@@ -67,67 +67,67 @@
(def: #export fresh Env (dict.new number.Hash<Nat>))
(def: (run' env types poly)
- (All [a] (-> Env (List Type) (Poly a) (e.Error a)))
+ (All [a] (-> Env (List Type) (Poly a) (Error a)))
(case (p.run [env types] poly)
- (#e.Error error)
- (#e.Error error)
+ (#error.Failure error)
+ (#error.Failure error)
- (#e.Success [[env' remaining] output])
+ (#error.Success [[env' remaining] output])
(case remaining
#.Nil
- (#e.Success output)
+ (#error.Success output)
_
(ex.throw unconsumed remaining))))
(def: #export (run type poly)
- (All [a] (-> Type (Poly a) (e.Error a)))
+ (All [a] (-> Type (Poly a) (Error a)))
(run' fresh (list type) poly))
(def: #export env
(Poly Env)
(.function (_ [env inputs])
- (#e.Success [[env inputs] env])))
+ (#error.Success [[env inputs] env])))
(def: (with-env temp poly)
(All [a] (-> Env (Poly a) (Poly a)))
(.function (_ [env inputs])
(case (p.run [temp inputs] poly)
- (#e.Error error)
- (#e.Error error)
+ (#error.Failure error)
+ (#error.Failure error)
- (#e.Success [[_ remaining] output])
- (#e.Success [[env remaining] output]))))
+ (#error.Success [[_ remaining] output])
+ (#error.Success [[env remaining] output]))))
(def: #export peek
(Poly Type)
(.function (_ [env inputs])
(case inputs
#.Nil
- (#e.Error "Empty stream of types.")
+ (#error.Failure "Empty stream of types.")
(#.Cons headT tail)
- (#e.Success [[env inputs] headT]))))
+ (#error.Success [[env inputs] headT]))))
(def: #export any
(Poly Type)
(.function (_ [env inputs])
(case inputs
#.Nil
- (#e.Error "Empty stream of types.")
+ (#error.Failure "Empty stream of types.")
(#.Cons headT tail)
- (#e.Success [[env tail] headT]))))
+ (#error.Success [[env tail] headT]))))
(def: #export (local types poly)
(All [a] (-> (List Type) (Poly a) (Poly a)))
(.function (_ [env pass-through])
(case (run' env types poly)
- (#e.Error error)
- (#e.Error error)
+ (#error.Failure error)
+ (#error.Failure error)
- (#e.Success output)
- (#e.Success [[env pass-through] output]))))
+ (#error.Success output)
+ (#error.Success [[env pass-through] output]))))
(def: (label idx)
(-> Nat Code)
@@ -141,11 +141,11 @@
(case (p.run [(dict.put current-id [type g!var] env)
inputs]
poly)
- (#e.Error error)
- (#e.Error error)
+ (#error.Failure error)
+ (#error.Failure error)
- (#e.Success [[_ inputs'] output])
- (#e.Success [[env inputs'] [g!var output]])))))
+ (#error.Success [[_ inputs'] output])
+ (#error.Success [[env inputs'] [g!var output]])))))
(do-template [<name> <flattener> <tag> <exception>]
[(def: #export (<name> poly)
diff --git a/stdlib/source/lux/macro/syntax.lux b/stdlib/source/lux/macro/syntax.lux
index edee25af3..02c3ad1ae 100644
--- a/stdlib/source/lux/macro/syntax.lux
+++ b/stdlib/source/lux/macro/syntax.lux
@@ -40,7 +40,7 @@
(Syntax Code)
(function (_ tokens)
(case tokens
- #.Nil (#error.Error "There are no tokens to parse!")
+ #.Nil (#error.Failure "There are no tokens to parse!")
(#.Cons [t tokens']) (#error.Success [tokens' t]))))
(do-template [<get-name> <type> <tag> <eq> <desc>]
@@ -53,7 +53,7 @@
(#error.Success [tokens' x])
_
- (#error.Error ($_ text/compose "Cannot parse " <desc> (remaining-inputs tokens))))))]
+ (#error.Failure ($_ text/compose "Cannot parse " <desc> (remaining-inputs tokens))))))]
[ bit Bit #.Bit bit.Equivalence<Bit> "bit"]
[ nat Nat #.Nat number.Equivalence<Nat> "nat"]
@@ -88,11 +88,11 @@
(#.Cons [token tokens'])
(if (code/= ast token)
(#error.Success [tokens' []])
- (#error.Error ($_ text/compose "Expected a " (code.to-text ast) " but instead got " (code.to-text token)
- (remaining-inputs tokens))))
+ (#error.Failure ($_ text/compose "Expected a " (code.to-text ast) " but instead got " (code.to-text token)
+ (remaining-inputs tokens))))
_
- (#error.Error "There are no tokens to parse!"))))
+ (#error.Failure "There are no tokens to parse!"))))
(do-template [<name> <tag> <desc>]
[(def: #export <name>
@@ -104,7 +104,7 @@
(#error.Success [tokens' x])
_
- (#error.Error ($_ text/compose "Cannot parse local " <desc> (remaining-inputs tokens))))))]
+ (#error.Failure ($_ text/compose "Cannot parse local " <desc> (remaining-inputs tokens))))))]
[local-identifier #.Identifier "identifier"]
[ local-tag #.Tag "tag"]
@@ -120,10 +120,10 @@
(#.Cons [[_ (<tag> members)] tokens'])
(case (p members)
(#error.Success [#.Nil x]) (#error.Success [tokens' x])
- _ (#error.Error ($_ text/compose "Syntax was expected to fully consume " <desc> (remaining-inputs tokens))))
+ _ (#error.Failure ($_ text/compose "Syntax was expected to fully consume " <desc> (remaining-inputs tokens))))
_
- (#error.Error ($_ text/compose "Cannot parse " <desc> (remaining-inputs tokens))))))]
+ (#error.Failure ($_ text/compose "Cannot parse " <desc> (remaining-inputs tokens))))))]
[ form #.Form "form"]
[tuple #.Tuple "tuple"]
@@ -138,10 +138,10 @@
(#.Cons [[_ (#.Record pairs)] tokens'])
(case (p (join-pairs pairs))
(#error.Success [#.Nil x]) (#error.Success [tokens' x])
- _ (#error.Error ($_ text/compose "Syntax was expected to fully consume record" (remaining-inputs tokens))))
+ _ (#error.Failure ($_ text/compose "Syntax was expected to fully consume record" (remaining-inputs tokens))))
_
- (#error.Error ($_ text/compose "Cannot parse record" (remaining-inputs tokens))))))
+ (#error.Failure ($_ text/compose "Cannot parse record" (remaining-inputs tokens))))))
(def: #export end!
{#.doc "Ensures there are no more inputs."}
@@ -149,7 +149,7 @@
(function (_ tokens)
(case tokens
#.Nil (#error.Success [tokens []])
- _ (#error.Error ($_ text/compose "Expected list of tokens to be empty!" (remaining-inputs tokens))))))
+ _ (#error.Failure ($_ text/compose "Expected list of tokens to be empty!" (remaining-inputs tokens))))))
(def: #export end?
{#.doc "Checks whether there are no more inputs."}
@@ -163,8 +163,8 @@
(All [a] (-> (Error a) (Syntax a)))
(function (_ input)
(case outcome
- (#error.Error error)
- (#error.Error error)
+ (#error.Failure error)
+ (#error.Failure error)
(#error.Success value)
(#error.Success [input value])
@@ -173,8 +173,8 @@
(def: #export (run inputs syntax)
(All [a] (-> (List Code) (Syntax a) (Error a)))
(case (syntax inputs)
- (#error.Error error)
- (#error.Error error)
+ (#error.Failure error)
+ (#error.Failure error)
(#error.Success [unconsumed value])
(case unconsumed
@@ -182,9 +182,9 @@
(#error.Success value)
_
- (#error.Error (text/compose "Unconsumed inputs: "
- (|> (list/map code.to-text unconsumed)
- (text.join-with ", ")))))))
+ (#error.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."}
@@ -264,8 +264,8 @@
({(#error.Success (~ g!body))
((~ g!body) (~ g!state))
- (#error.Error (~ g!error))
- (#error.Error ((~! text.join-with) ": " (list (~ error-msg) (~ g!error))))}
+ (#error.Failure (~ g!error))
+ (#error.Failure ((~! text.join-with) ": " (list (~ error-msg) (~ g!error))))}
((~! ..run) (~ g!tokens)
(: ((~! ..Syntax) (Meta (List Code)))
((~! do) (~! p.Monad<Parser>)
diff --git a/stdlib/source/lux/math/modular.lux b/stdlib/source/lux/math/modular.lux
index ac141a3c9..6222ed87b 100644
--- a/stdlib/source/lux/math/modular.lux
+++ b/stdlib/source/lux/math/modular.lux
@@ -6,7 +6,7 @@
[codec (#+ Codec)]
[monad (#+ do)]]
[data
- ["e" error (#+ Error)]
+ ["." error (#+ Error)]
["." number ("int/." Codec<Text,Int>)]
[text ("text/." Monoid<Text>)
["l" lexer (#+ Lexer)]]]
@@ -28,7 +28,7 @@
(Ex [m] (-> Int (Error (Modulus m))))
(if (i/= +0 value)
(ex.throw zero-cannot-be-a-modulus [])
- (#e.Success (:abstraction value))))
+ (#error.Success (:abstraction value))))
(def: #export (to-int modulus)
(All [m] (-> (Modulus m) Int))
@@ -54,10 +54,10 @@
(syntax: #export (modulus {modulus s.int})
(case (from-int modulus)
- (#e.Success _)
- (wrap (list (` (e.assume (..from-int (~ (code.int modulus)))))))
+ (#error.Success _)
+ (wrap (list (` (error.assume (..from-int (~ (code.int modulus)))))))
- (#e.Error error)
+ (#error.Failure error)
(p.fail error)))
(def: intL
@@ -108,8 +108,8 @@
[sample sample-modulus] (:representation sample)]
(if (i/= (to-int reference-modulus)
(to-int sample-modulus))
- (#e.Success (:abstraction {#remainder sample
- #modulus reference-modulus}))
+ (#error.Success (:abstraction {#remainder sample
+ #modulus reference-modulus}))
(ex.throw cannot-equalize-moduli [reference-modulus sample-modulus]))))
(do-template [<name> <op>]
diff --git a/stdlib/source/lux/platform/compiler/default/init.lux b/stdlib/source/lux/platform/compiler/default/init.lux
index 699ddfb54..012ab3ea9 100644
--- a/stdlib/source/lux/platform/compiler/default/init.lux
+++ b/stdlib/source/lux/platform/compiler/default/init.lux
@@ -98,8 +98,8 @@
(-> Reader (analysis.Operation Code))
(function (_ [bundle compiler])
(case (reader (get@ #.source compiler))
- (#error.Error error)
- (#error.Error error)
+ (#error.Failure error)
+ (#error.Failure error)
(#error.Success [source' output])
(let [[cursor _] output]
@@ -144,10 +144,10 @@
(#error.Success [state' output])
(recur state')
- (#error.Error error)
+ (#error.Failure error)
(if (ex.match? syntax.end-of-file error)
(#error.Success [state []])
- (ex.with-stack ///.cannot-compile module (#error.Error error))))))))
+ (ex.with-stack ///.cannot-compile module (#error.Failure error))))))))
(def: (compile hash input)
(-> Nat ///.Input <Operation>)
diff --git a/stdlib/source/lux/platform/compiler/default/platform.lux b/stdlib/source/lux/platform/compiler/default/platform.lux
index 9a169fb15..10dfd6ebb 100644
--- a/stdlib/source/lux/platform/compiler/default/platform.lux
+++ b/stdlib/source/lux/platform/compiler/default/platform.lux
@@ -73,7 +73,7 @@
## (wrap (|> state
## (set@ [#.info #.mode] #.Build))))
- ## (#error.Error error)
+ ## (#error.Failure error)
## (io.fail error))
)
@@ -88,8 +88,8 @@
## _ (write-module target-dir file-name (get@ #cli.module configuration) module outputs)
]
## (case (compiler input)
- ## (#error.Error error)
- ## (:: (get@ #file-system platform) lift (#error.Error error))
+ ## (#error.Failure error)
+ ## (:: (get@ #file-system platform) lift (#error.Failure error))
## (#error.Success))
(let [compiler (init.compiler syntax.prelude state)
@@ -99,11 +99,11 @@
(#error.Success more|done)
(case more|done
(#.Left more)
- (:: (get@ #file-system platform) lift (#error.Error "NOT DONE!"))
+ (:: (get@ #file-system platform) lift (#error.Failure "NOT DONE!"))
(#.Right done)
(wrap []))
- (#error.Error error)
- (:: (get@ #file-system platform) lift (#error.Error error))))))
+ (#error.Failure error)
+ (:: (get@ #file-system platform) lift (#error.Failure error))))))
)
diff --git a/stdlib/source/lux/platform/compiler/default/syntax.lux b/stdlib/source/lux/platform/compiler/default/syntax.lux
index 5e1990393..a1bb9f3ea 100644
--- a/stdlib/source/lux/platform/compiler/default/syntax.lux
+++ b/stdlib/source/lux/platform/compiler/default/syntax.lux
@@ -187,15 +187,15 @@
(#error.Success [source' top])
(recur source' (#.Cons top stack))
- (#error.Error error)
+ (#error.Failure error)
(let [[where offset _] source]
(case (read-close (char <close>) source-code//size source-code offset)
(#error.Success offset')
(#error.Success [[(update@ #.column inc where) offset' source-code]
[where (<tag> (list.reverse stack))]])
- (#error.Error error)
- (#error.Error error)))))))]
+ (#error.Failure error)
+ (#error.Failure error)))))))]
## Form and tuple syntax is mostly the same, differing only in the
## delimiters involved.
@@ -216,19 +216,19 @@
(#error.Success [sourceFV value])
(recur sourceFV (#.Cons [field value] stack))
- (#error.Error error)
- (#error.Error error))
+ (#error.Failure error)
+ (#error.Failure error))
- (#error.Error error)
+ (#error.Failure error)
(let [[where offset _] source]
- (<| (!with-char+ source-code//size source-code offset closing-char (#error.Error error))
+ (<| (!with-char+ source-code//size source-code offset closing-char (#error.Failure error))
(case (read-close (`` (char (~~ (static ..close-record)))) source-code//size source-code offset)
(#error.Success offset')
(#error.Success [[(update@ #.column inc where) offset' source-code]
[where (#.Record (list.reverse stack))]])
- (#error.Error error)
- (#error.Error error))))))))
+ (#error.Failure error)
+ (#error.Failure error))))))))
(template: (!guarantee-no-new-lines content body)
(case ("lux text index" content (static text.new-line) 0)
@@ -297,8 +297,8 @@
source-code]
[where (<tag> output)]])
- (#error.Error error)
- (#error.Error error)))
+ (#error.Failure error)
+ (#error.Failure error)))
(def: no-exponent Offset 0)
@@ -382,7 +382,7 @@
(with-expansions [<end-of-file> (ex.throw end-of-file current-module)
<failure> (ex.throw unrecognized-input [where "General" source-code offset/0])
- <close!> (#error.Error close-signal)
+ <close!> (#error.Failure close-signal)
<consume-1> (as-is [where (!inc offset/0) source-code])
<consume-2> (as-is [where (!inc/2 offset/0) source-code])]
@@ -392,8 +392,8 @@
(#error.Success [source' name])
(#error.Success [source' [@module name]])
- (#error.Error error)
- (#error.Error error))
+ (#error.Failure error)
+ (#error.Failure error))
## else
<failure>))
@@ -412,8 +412,8 @@
(#error.Success [source' name])
(#error.Success [source' [@where (@tag name)]])
- (#error.Error error)
- (#error.Error error)))
+ (#error.Failure error)
+ (#error.Failure error)))
(with-expansions [<simple> (as-is (#error.Success [source' ["" simple]]))]
(`` (def: (parse-full-name start source)
@@ -428,20 +428,20 @@
(#error.Success [source'' complex])
(#error.Success [source'' [simple complex]])
- (#error.Error error)
- (#error.Error error)))
+ (#error.Failure error)
+ (#error.Failure error)))
<simple>)))
- (#error.Error error)
- (#error.Error error)))))
+ (#error.Failure error)
+ (#error.Failure error)))))
(template: (!parse-full-name @offset @source @where @tag)
(case (..parse-full-name @offset @source)
(#error.Success [source' full-name])
(#error.Success [source' [@where (@tag full-name)]])
- (#error.Error error)
- (#error.Error error)))
+ (#error.Failure error)
+ (#error.Failure error)))
(`` (template: (<<closers>>)
[(~~ (static ..close-form))
diff --git a/stdlib/source/lux/platform/compiler/meta/cache.lux b/stdlib/source/lux/platform/compiler/meta/cache.lux
index bcb7c98f0..ceed96164 100644
--- a/stdlib/source/lux/platform/compiler/meta/cache.lux
+++ b/stdlib/source/lux/platform/compiler/meta/cache.lux
@@ -137,7 +137,7 @@
(#error.Success [dependency document])
(wrap (#.Some [dependency document]))
- (#error.Error error)
+ (#error.Failure error)
(do @
[_ (un-install System<m> root module)]
(wrap #.None)))))
diff --git a/stdlib/source/lux/platform/compiler/meta/io/archive.lux b/stdlib/source/lux/platform/compiler/meta/io/archive.lux
index 1f0714b25..354f84460 100644
--- a/stdlib/source/lux/platform/compiler/meta/io/archive.lux
+++ b/stdlib/source/lux/platform/compiler/meta/io/archive.lux
@@ -54,7 +54,7 @@
(#error.Success output)
(wrap output)
- (#error.Error _)
+ (#error.Failure _)
(:: System<m> throw cannot-prepare [archive module]))))))
(def: #export (write System<m> root content name)
diff --git a/stdlib/source/lux/platform/compiler/meta/io/context.lux b/stdlib/source/lux/platform/compiler/meta/io/context.lux
index 32e05c219..be72e4ccc 100644
--- a/stdlib/source/lux/platform/compiler/meta/io/context.lux
+++ b/stdlib/source/lux/platform/compiler/meta/io/context.lux
@@ -103,5 +103,5 @@
#////.file file
#////.code code})
- (#error.Error _)
+ (#error.Failure _)
(:: System<m> throw ..cannot-read-module [module])))))
diff --git a/stdlib/source/lux/platform/compiler/phase/analysis.lux b/stdlib/source/lux/platform/compiler/phase/analysis.lux
index c69ff8eb2..c5256436f 100644
--- a/stdlib/source/lux/platform/compiler/phase/analysis.lux
+++ b/stdlib/source/lux/platform/compiler/phase/analysis.lux
@@ -253,8 +253,8 @@
(#error.Success [[bundle' (set@ #.source old-source state')]
output])
- (#error.Error error)
- (#error.Error error)))))
+ (#error.Failure error)
+ (#error.Failure error)))))
(def: fresh-bindings
(All [k v] (Bindings k v))
@@ -279,10 +279,10 @@
[head output]])
#.Nil
- (#error.Error "Impossible error: Drained scopes!"))
+ (#error.Failure "Impossible error: Drained scopes!"))
- (#error.Error error)
- (#error.Error error))))
+ (#error.Failure error)
+ (#error.Failure error))))
(def: #export (with-current-module name)
(All [a] (-> Text (Operation a) (Operation a)))
@@ -301,9 +301,9 @@
(#error.Success [[bundle' (set@ #.cursor old-cursor state')]
output])
- (#error.Error error)
- (#error.Error (format "@ " (%cursor cursor) text.new-line
- error)))))))
+ (#error.Failure error)
+ (#error.Failure (format "@ " (%cursor cursor) text.new-line
+ error)))))))
(do-template [<name> <type> <field> <value>]
[(def: #export (<name> value)
diff --git a/stdlib/source/lux/platform/compiler/phase/analysis/case.lux b/stdlib/source/lux/platform/compiler/phase/analysis/case.lux
index 5044aed92..d7b020932 100644
--- a/stdlib/source/lux/platform/compiler/phase/analysis/case.lux
+++ b/stdlib/source/lux/platform/compiler/phase/analysis/case.lux
@@ -292,7 +292,7 @@
(///.assert non-exhaustive-pattern-matching [inputC branches coverage]
(coverage.exhaustive? coverage))
- (#error.Error error)
+ (#error.Failure error)
(///.fail error))]
(wrap (#//.Case inputA [outputH outputT])))
diff --git a/stdlib/source/lux/platform/compiler/phase/analysis/case/coverage.lux b/stdlib/source/lux/platform/compiler/phase/analysis/case/coverage.lux
index aff981e09..bdf524f73 100644
--- a/stdlib/source/lux/platform/compiler/phase/analysis/case/coverage.lux
+++ b/stdlib/source/lux/platform/compiler/phase/analysis/case/coverage.lux
@@ -336,7 +336,7 @@
_
(wrap [(#.Some altMSF) altsSF']))
- (#error.Error error)
+ (#error.Failure error)
(error.fail error))
))))]
[successA possibilitiesSF] (fuse-once addition (flatten-alt so-far))]
diff --git a/stdlib/source/lux/platform/compiler/phase/analysis/macro.lux b/stdlib/source/lux/platform/compiler/phase/analysis/macro.lux
index af12c747d..64dabaf43 100644
--- a/stdlib/source/lux/platform/compiler/phase/analysis/macro.lux
+++ b/stdlib/source/lux/platform/compiler/phase/analysis/macro.lux
@@ -64,7 +64,7 @@
(#error.Success output)
(#error.Success output)
- (#error.Error error)
+ (#error.Failure error)
((///.throw expansion-failed [name inputs error]) state)))))
(def: #export (expand-one name macro inputs)
diff --git a/stdlib/source/lux/platform/compiler/phase/analysis/scope.lux b/stdlib/source/lux/platform/compiler/phase/analysis/scope.lux
index 2849e059d..8cd55e198 100644
--- a/stdlib/source/lux/platform/compiler/phase/analysis/scope.lux
+++ b/stdlib/source/lux/platform/compiler/phase/analysis/scope.lux
@@ -130,8 +130,8 @@
_
(ex.throw invalid-scope-alteration []))
- (#e.Error error)
- (#e.Error error)))
+ (#e.Failure error)
+ (#e.Failure error)))
_
(ex.throw cannot-create-local-binding-without-a-scope []))
@@ -172,8 +172,8 @@
state')]
output])
- (#e.Error error)
- (#e.Error error)))
+ (#e.Failure error)
+ (#e.Failure error)))
))
(exception: #export (cannot-get-next-reference-when-there-is-no-scope)
diff --git a/stdlib/source/lux/platform/compiler/phase/analysis/type.lux b/stdlib/source/lux/platform/compiler/phase/analysis/type.lux
index 36fee29f8..c3219f5ac 100644
--- a/stdlib/source/lux/platform/compiler/phase/analysis/type.lux
+++ b/stdlib/source/lux/platform/compiler/phase/analysis/type.lux
@@ -25,7 +25,7 @@
(#error.Success [[bundle (set@ #.type-context context' state)]
output])
- (#error.Error error)
+ (#error.Failure error)
((///.fail error) stateE))))
(def: #export with-fresh-env
diff --git a/stdlib/source/lux/platform/compiler/phase/extension.lux b/stdlib/source/lux/platform/compiler/phase/extension.lux
index 75814ad24..ec7323b1e 100644
--- a/stdlib/source/lux/platform/compiler/phase/extension.lux
+++ b/stdlib/source/lux/platform/compiler/phase/extension.lux
@@ -94,8 +94,8 @@
(#error.Success [[bundle' state'] output])
(#error.Success [[bundle' (set old state')] output])
- (#error.Error error)
- (#error.Error error))))))
+ (#error.Failure error)
+ (#error.Failure error))))))
(def: #export (temporary transform)
(All [s i o v]
@@ -107,8 +107,8 @@
(#error.Success [[bundle' state'] output])
(#error.Success [[bundle' state] output])
- (#error.Error error)
- (#error.Error error)))))
+ (#error.Failure error)
+ (#error.Failure error)))))
(def: #export (with-state state)
(All [s i o v]
@@ -136,5 +136,5 @@
(#error.Success [state' output])
(#error.Success [[bundle state'] output])
- (#error.Error error)
- (#error.Error error))))
+ (#error.Failure error)
+ (#error.Failure error))))
diff --git a/stdlib/source/lux/platform/compiler/phase/extension/analysis/host.jvm.lux b/stdlib/source/lux/platform/compiler/phase/extension/analysis/host.jvm.lux
index a494b0e44..2981dc89b 100644
--- a/stdlib/source/lux/platform/compiler/phase/extension/analysis/host.jvm.lux
+++ b/stdlib/source/lux/platform/compiler/phase/extension/analysis/host.jvm.lux
@@ -6,7 +6,7 @@
["ex" exception (#+ exception:)]
pipe]
[data
- ["e" error]
+ ["." error (#+ Error)]
["." maybe]
["." product]
["." text ("text/." Equivalence<Text>)
@@ -485,10 +485,10 @@
(do ////.Monad<Operation>
[]
(case (Class::forName name)
- (#e.Success [class])
+ (#error.Success [class])
(wrap class)
- (#e.Error error)
+ (#error.Failure error)
(////.throw unknown-class name))))
(def: (sub-class? super sub)
@@ -759,7 +759,7 @@
(do ////.Monad<Operation>
[class (load-class class-name)]
(case (Class::getDeclaredField field-name class)
- (#e.Success field)
+ (#error.Success field)
(let [owner (Field::getDeclaringClass field)]
(if (is? owner class)
(wrap [class field])
@@ -768,7 +768,7 @@
" Owner Class: " (Class::getName owner) text.new-line
"Target Class: " class-name text.new-line))))
- (#e.Error _)
+ (#error.Failure _)
(////.throw unknown-field (format class-name "#" field-name)))))
(def: (static-field class-name field-name)
@@ -1143,9 +1143,9 @@
(def: invoke::static
Handler
(function (_ extension-name analyse args)
- (case (: (e.Error [Text Text (List [Text Code])])
+ (case (: (Error [Text Text (List [Text Code])])
(s.run args ($_ p.and s.text s.text (p.some (s.tuple (p.and s.text s.any))))))
- (#e.Success [class method argsTC])
+ (#error.Success [class method argsTC])
(do ////.Monad<Operation>
[#let [argsT (list/map product.left argsTC)]
[methodT exceptionsT] (method-candidate class method #Static argsT)
@@ -1160,9 +1160,9 @@
(def: invoke::virtual
Handler
(function (_ extension-name analyse args)
- (case (: (e.Error [Text Text Code (List [Text Code])])
+ (case (: (Error [Text Text Code (List [Text Code])])
(s.run args ($_ p.and s.text s.text s.any (p.some (s.tuple (p.and s.text s.any))))))
- (#e.Success [class method objectC argsTC])
+ (#error.Success [class method objectC argsTC])
(do ////.Monad<Operation>
[#let [argsT (list/map product.left argsTC)]
[methodT exceptionsT] (method-candidate class method #Virtual argsT)
@@ -1183,9 +1183,9 @@
(def: invoke::special
Handler
(function (_ extension-name analyse args)
- (case (: (e.Error [(List Code) [Text Text Code (List [Text Code]) Any]])
+ (case (: (Error [(List Code) [Text Text Code (List [Text Code]) Any]])
(p.run args ($_ p.and s.text s.text s.any (p.some (s.tuple (p.and s.text s.any))) s.end!)))
- (#e.Success [_ [class method objectC argsTC _]])
+ (#error.Success [_ [class method objectC argsTC _]])
(do ////.Monad<Operation>
[#let [argsT (list/map product.left argsTC)]
[methodT exceptionsT] (method-candidate class method #Special argsT)
@@ -1200,9 +1200,9 @@
(def: invoke::interface
Handler
(function (_ extension-name analyse args)
- (case (: (e.Error [Text Text Code (List [Text Code])])
+ (case (: (Error [Text Text Code (List [Text Code])])
(s.run args ($_ p.and s.text s.text s.any (p.some (s.tuple (p.and s.text s.any))))))
- (#e.Success [class-name method objectC argsTC])
+ (#error.Success [class-name method objectC argsTC])
(do ////.Monad<Operation>
[#let [argsT (list/map product.left argsTC)]
class (load-class class-name)
@@ -1221,9 +1221,9 @@
(def: invoke::constructor
Handler
(function (_ extension-name analyse args)
- (case (: (e.Error [Text (List [Text Code])])
+ (case (: (Error [Text (List [Text Code])])
(s.run args ($_ p.and s.text (p.some (s.tuple (p.and s.text s.any))))))
- (#e.Success [class argsTC])
+ (#error.Success [class argsTC])
(do ////.Monad<Operation>
[#let [argsT (list/map product.left argsTC)]
[methodT exceptionsT] (constructor-candidate class argsT)
diff --git a/stdlib/source/lux/platform/compiler/phase/synthesis/expression.lux b/stdlib/source/lux/platform/compiler/phase/synthesis/expression.lux
index 0d15ae463..672bc9e87 100644
--- a/stdlib/source/lux/platform/compiler/phase/synthesis/expression.lux
+++ b/stdlib/source/lux/platform/compiler/phase/synthesis/expression.lux
@@ -78,7 +78,7 @@
(case> (#error.Success output)
(#error.Success output)
- (#error.Error error)
+ (#error.Failure error)
(<| (///.run' state)
(do ///.Monad<Operation>
[argsS+ (monad.map @ phase args)]
diff --git a/stdlib/source/lux/platform/compiler/phase/translation.lux b/stdlib/source/lux/platform/compiler/phase/translation.lux
index fb40f4652..c7fb60c08 100644
--- a/stdlib/source/lux/platform/compiler/phase/translation.lux
+++ b/stdlib/source/lux/platform/compiler/phase/translation.lux
@@ -108,8 +108,8 @@
(#error.Success [[bundle' (set@ #context [old-scope (inc old-inner)] state')]
[new-scope output]])
- (#error.Error error)
- (#error.Error error)))))
+ (#error.Failure error)
+ (#error.Failure error)))))
(def: #export context
(All [anchor expression statement]
@@ -129,8 +129,8 @@
(#error.Success [[bundle' (set@ <tag> (get@ <tag> state) state')]
output])
- (#error.Error error)
- (#error.Error error)))))
+ (#error.Failure error)
+ (#error.Failure error)))))
(def: #export <get>
(All [anchor expression statement]
@@ -180,7 +180,7 @@
(#error.Success output)
(#error.Success [state+ output])
- (#error.Error error)
+ (#error.Failure error)
(ex.throw cannot-interpret error))))]
[evaluate! expression]
@@ -195,7 +195,7 @@
(#error.Success output)
(#error.Success [stateE output])
- (#error.Error error)
+ (#error.Failure error)
(ex.throw cannot-interpret error))))
(def: #export (save! name code)
diff --git a/stdlib/source/lux/platform/interpreter.lux b/stdlib/source/lux/platform/interpreter.lux
index b73f72bc6..a75cbc01e 100644
--- a/stdlib/source/lux/platform/interpreter.lux
+++ b/stdlib/source/lux/platform/interpreter.lux
@@ -132,7 +132,7 @@
(#error.Success [state' output])
(#error.Success [state' output])
- (#error.Error error)
+ (#error.Failure error)
(if (ex.match? total.not-a-statement error)
(<| (phase.run' state)
(:share [anchor expression statement]
@@ -140,7 +140,7 @@
state}
{<Interpretation>
(interpret-expression code)}))
- (#error.Error error)))))
+ (#error.Failure error)))))
)
(def: (execute configuration code)
@@ -213,7 +213,7 @@
[_ (:: Console<!> write representation)]
(recur context' #0))
- (#error.Error error)
+ (#error.Failure error)
(if (ex.match? syntax.end-of-file error)
(recur context #1)
(exec (log! (ex.construct ..error error))
diff --git a/stdlib/source/lux/platform/interpreter/type.lux b/stdlib/source/lux/platform/interpreter/type.lux
index 7d3ac0d9c..698238e1c 100644
--- a/stdlib/source/lux/platform/interpreter/type.lux
+++ b/stdlib/source/lux/platform/interpreter/type.lux
@@ -144,7 +144,7 @@
#.None
representation)
- (#error.Error error)
+ (#error.Failure error)
(p.fail error))))
(def: (tuple-representation representation)
@@ -199,5 +199,5 @@
(ex.report ["Type" (%type type)]
["Value" (representation value)])
- (#error.Error error)
+ (#error.Failure error)
(ex.construct cannot-represent-value [type])))
diff --git a/stdlib/source/lux/time/date.lux b/stdlib/source/lux/time/date.lux
index 0e8f5468a..71dd1003d 100644
--- a/stdlib/source/lux/time/date.lux
+++ b/stdlib/source/lux/time/date.lux
@@ -8,7 +8,7 @@
["p" parser]
[monad (#+ do)]]
[data
- ["e" error]
+ ["." error (#+ Error)]
["." maybe]
["." number ("int/." Codec<Text,Int>)]
[text ("text/." Monoid<Text>)
@@ -314,7 +314,7 @@
#day (.nat utc-day)})))
(def: (decode input)
- (-> Text (e.Error Date))
+ (-> Text (Error Date))
(l.run input lex-date))
(structure: #export _
diff --git a/stdlib/source/lux/time/instant.lux b/stdlib/source/lux/time/instant.lux
index 08029405a..8c61abe5c 100644
--- a/stdlib/source/lux/time/instant.lux
+++ b/stdlib/source/lux/time/instant.lux
@@ -9,7 +9,7 @@
[monad (#+ do Monad)]
["p" parser]]
[data
- ["e" error]
+ ["." error (#+ Error)]
["." maybe]
["." number ("int/." Codec<Text,Int>)]
[text ("text/." Monoid<Text>)
@@ -300,7 +300,7 @@
## (shift (duration.scale-up utc-millis duration.milli))))))
## (def: (decode input)
-## (-> Text (e.Error Instant))
+## (-> Text (Error Instant))
## (l.run input lex-instant))
## (structure: #export _
diff --git a/stdlib/source/lux/type/check.lux b/stdlib/source/lux/type/check.lux
index 7d2e55982..fa6067ab6 100644
--- a/stdlib/source/lux/type/check.lux
+++ b/stdlib/source/lux/type/check.lux
@@ -58,8 +58,8 @@
(#error.Success [context' output])
(#error.Success [context' (f output)])
- (#error.Error error)
- (#error.Error error)))))
+ (#error.Failure error)
+ (#error.Failure error)))))
(structure: #export _ (Apply Check)
(def: functor Functor<Check>)
@@ -72,11 +72,11 @@
(#error.Success [context'' a])
(#error.Success [context'' (f a)])
- (#error.Error error)
- (#error.Error error))
+ (#error.Failure error)
+ (#error.Failure error))
- (#error.Error error)
- (#error.Error error)
+ (#error.Failure error)
+ (#error.Failure error)
)))
)
@@ -95,11 +95,11 @@
(#error.Success [context'' a])
(#error.Success [context'' a])
- (#error.Error error)
- (#error.Error error))
+ (#error.Failure error)
+ (#error.Failure error))
- (#error.Error error)
- (#error.Error error)
+ (#error.Failure error)
+ (#error.Failure error)
)))
)
@@ -155,8 +155,8 @@
(#error.Success [context' output])
(#error.Success output)
- (#error.Error error)
- (#error.Error error)))
+ (#error.Failure error)
+ (#error.Failure error)))
(def: #export (throw exception message)
(All [e a] (-> (ex.Exception e) e (Check a)))
@@ -299,20 +299,20 @@
(#error.Success [context' output])
(#error.Success [context' (#.Some output)])
- (#error.Error _)
+ (#error.Failure _)
(#error.Success [context #.None]))))
(def: #export (fail message)
(All [a] (-> Text (Check a)))
(function (_ context)
- (#error.Error message)))
+ (#error.Failure message)))
(def: #export (assert message test)
(-> Text Bit (Check Any))
(function (_ context)
(if test
(#error.Success [context []])
- (#error.Error message))))
+ (#error.Failure message))))
(def: (either left right)
(All [a] (-> (Check a) (Check a) (Check a)))
@@ -321,7 +321,7 @@
(#error.Success [context' output])
(#error.Success [context' output])
- (#error.Error _)
+ (#error.Failure _)
(right context))))
(def: (assumed? [e a] assumptions)
@@ -441,18 +441,18 @@
(All [a] (-> (-> Any Text) (Check a) (Check a)))
(function (_ context)
(case (check context)
- (#error.Error error)
- (#error.Error (case error
- ""
- (on-error [])
-
- _
- ($_ text/compose
- (on-error [])
- text.new-line text.new-line
- "-----------------------------------------"
- text.new-line text.new-line
- error)))
+ (#error.Failure error)
+ (#error.Failure (case error
+ ""
+ (on-error [])
+
+ _
+ ($_ text/compose
+ (on-error [])
+ text.new-line text.new-line
+ "-----------------------------------------"
+ text.new-line text.new-line
+ error)))
output
output)))
@@ -628,7 +628,7 @@
{#.doc "A simple type-checking function that just returns a yes/no answer."}
(-> Type Type Bit)
(case (run fresh-context (check' (list) expected actual))
- (#error.Error _)
+ (#error.Failure _)
#0
(#error.Success _)
diff --git a/stdlib/source/lux/type/quotient.lux b/stdlib/source/lux/type/quotient.lux
index 17780e622..994383744 100644
--- a/stdlib/source/lux/type/quotient.lux
+++ b/stdlib/source/lux/type/quotient.lux
@@ -4,7 +4,7 @@
[monad (#+ do)]
["p" parser]]
[data
- ["e" error (#+ Error)]]
+ ["." error (#+ Error)]]
["." type
abstract]
["." macro
@@ -62,9 +62,9 @@
(do @
[constructorT (macro.find-type quotient)
quotientT (case (quotient-type constructorT)
- (#e.Success quotientT)
+ (#error.Success quotientT)
(wrap quotientT)
- (#e.Error error)
+ (#error.Failure error)
(p.fail error))]
(wrap (list (type.to-code quotientT)))))
diff --git a/stdlib/source/lux/type/refinement.lux b/stdlib/source/lux/type/refinement.lux
index 1013cf283..4ccfd02be 100644
--- a/stdlib/source/lux/type/refinement.lux
+++ b/stdlib/source/lux/type/refinement.lux
@@ -5,7 +5,7 @@
[monad (#+ do)]
["p" parser]]
[data
- ["e" error (#+ Error)]]
+ ["." error (#+ Error)]]
["." type ("type/." Equivalence<Type>)
abstract]
["." macro
@@ -96,9 +96,9 @@
(do @
[constructorT (macro.find-type refinement)
refinementT (case (refinement-type constructorT)
- (#e.Success refinementT)
+ (#error.Success refinementT)
(wrap refinementT)
- (#e.Error error)
+ (#error.Failure error)
(p.fail error))]
(wrap (list (type.to-code refinementT)))))
diff --git a/stdlib/source/lux/world/file.lux b/stdlib/source/lux/world/file.lux
index ac033fd89..343d2f7aa 100644
--- a/stdlib/source/lux/world/file.lux
+++ b/stdlib/source/lux/world/file.lux
@@ -347,12 +347,12 @@
(#error.Success file)
(wrap true)
- (#error.Error _)
+ (#error.Failure _)
(do Monad<!>
[?directory (:: System<!> directory path)]
(case ?directory
(#error.Success directory)
(wrap true)
- (#error.Error _)
+ (#error.Failure _)
(wrap false))))))
diff --git a/stdlib/source/lux/world/net/tcp.jvm.lux b/stdlib/source/lux/world/net/tcp.jvm.lux
index f9bde2e2c..cd8543f3a 100644
--- a/stdlib/source/lux/world/net/tcp.jvm.lux
+++ b/stdlib/source/lux/world/net/tcp.jvm.lux
@@ -113,7 +113,7 @@
[socket (ServerSocket::accept server)]
(io.io (tcp socket)))]
(case ?client
- (#error.Error error)
+ (#error.Failure error)
(wrap [])
(#error.Success client)