aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/control
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/lux/control')
-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
6 files changed, 117 insertions, 103 deletions
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)]))))