diff options
author | Eduardo Julian | 2019-07-02 23:36:02 -0400 |
---|---|---|
committer | Eduardo Julian | 2019-07-02 23:36:02 -0400 |
commit | 91c0619657bcf2ac520e7dd2912188f66bbe2157 (patch) | |
tree | f26675f263eb5f0285c1674b0777a7369248fe07 /stdlib/source/lux/tool | |
parent | 4f191540f831a7bba0e262b1a6b598f99fb9b35c (diff) |
Re-name "lux/data/error" to "lux/control/try".
Diffstat (limited to 'stdlib/source/lux/tool')
32 files changed, 298 insertions, 304 deletions
diff --git a/stdlib/source/lux/tool/compiler.lux b/stdlib/source/lux/tool/compiler.lux index f855d6db0..ca9ea4a0e 100644 --- a/stdlib/source/lux/tool/compiler.lux +++ b/stdlib/source/lux/tool/compiler.lux @@ -1,9 +1,9 @@ (.module: [lux (#- Module Code) [control + ["." try (#+ Try)] ["." exception (#+ exception:)]] [data - ["." error (#+ Error)] ["." text] [collection ["." dictionary (#+ Dictionary)]]] @@ -38,8 +38,8 @@ (type: #export (Compilation s d o) {#dependencies (List Module) #process (-> s Archive - (Error [s (Either (Compilation s d o) - [[Descriptor (Document d)] (Output o)])]))}) + (Try [s (Either (Compilation s d o) + [[Descriptor (Document d)] (Output o)])]))}) (type: #export (Compiler s d o) (-> Input (Compilation s d o))) diff --git a/stdlib/source/lux/tool/compiler/analysis.lux b/stdlib/source/lux/tool/compiler/analysis.lux index 05bb2be01..f2e1cb978 100644 --- a/stdlib/source/lux/tool/compiler/analysis.lux +++ b/stdlib/source/lux/tool/compiler/analysis.lux @@ -4,10 +4,10 @@ [monad (#+ do)]] [control ["." function] + ["." try] ["." exception (#+ Exception)]] [data ["." product] - ["." error] ["." maybe] ["." text ("#@." equivalence) ["%" format (#+ Format format)]] @@ -250,12 +250,12 @@ (function (_ [bundle state]) (let [old-source (get@ #.source state)] (case (action [bundle (set@ #.source source state)]) - (#error.Success [[bundle' state'] output]) - (#error.Success [[bundle' (set@ #.source old-source state')] - output]) + (#try.Success [[bundle' state'] output]) + (#try.Success [[bundle' (set@ #.source old-source state')] + output]) - (#error.Failure error) - (#error.Failure error))))) + (#try.Failure error) + (#try.Failure error))))) (def: fresh-bindings (All [k v] (Bindings k v)) @@ -273,17 +273,17 @@ (All [a] (-> (Operation a) (Operation [Scope a]))) (function (_ [bundle state]) (case (action [bundle (update@ #.scopes (|>> (#.Cons fresh-scope)) state)]) - (#error.Success [[bundle' state'] output]) + (#try.Success [[bundle' state'] output]) (case (get@ #.scopes state') (#.Cons head tail) - (#error.Success [[bundle' (set@ #.scopes tail state')] - [head output]]) + (#try.Success [[bundle' (set@ #.scopes tail state')] + [head output]]) #.Nil - (#error.Failure "Impossible error: Drained scopes!")) + (#try.Failure "Impossible error: Drained scopes!")) - (#error.Failure error) - (#error.Failure error)))) + (#try.Failure error) + (#try.Failure error)))) (def: #export (with-current-module name) (All [a] (-> Text (Operation a) (Operation a))) @@ -298,12 +298,12 @@ (function (_ [bundle state]) (let [old-cursor (get@ #.cursor state)] (case (action [bundle (set@ #.cursor cursor state)]) - (#error.Success [[bundle' state'] output]) - (#error.Success [[bundle' (set@ #.cursor old-cursor state')] - output]) + (#try.Success [[bundle' state'] output]) + (#try.Success [[bundle' (set@ #.cursor old-cursor state')] + output]) - (#error.Failure error) - (#error.Failure error)))))) + (#try.Failure error) + (#try.Failure error)))))) (def: (locate-error cursor error) (-> Cursor Text Text) @@ -313,7 +313,7 @@ (def: #export (fail error) (-> Text Operation) (function (_ [bundle state]) - (#error.Failure (locate-error (get@ #.cursor state) error)))) + (#try.Failure (locate-error (get@ #.cursor state) error)))) (def: #export (throw exception parameters) (All [e] (-> (Exception e) e Operation)) @@ -322,7 +322,7 @@ (def: #export (fail' error) (-> Text (phase.Operation Lux)) (function (_ state) - (#error.Failure (locate-error (get@ #.cursor state) error)))) + (#try.Failure (locate-error (get@ #.cursor state) error)))) (def: #export (throw' exception parameters) (All [e] (-> (Exception e) e (phase.Operation Lux))) @@ -332,14 +332,14 @@ (All [e o] (-> (Exception e) e (Operation o) (Operation o))) (function (_ bundle,state) (case (action bundle,state) - (#error.Success output) - (#error.Success output) + (#try.Success output) + (#try.Success output) - (#error.Failure error) + (#try.Failure error) (let [[bundle state] bundle,state] - (#error.Failure (<| (locate-error (get@ #.cursor state)) - (exception.decorate (exception.construct exception message)) - error)))))) + (#try.Failure (<| (locate-error (get@ #.cursor state)) + (exception.decorate (exception.construct exception message)) + error)))))) (template [<name> <type> <field> <value>] [(def: #export (<name> value) diff --git a/stdlib/source/lux/tool/compiler/default/evaluation.lux b/stdlib/source/lux/tool/compiler/default/evaluation.lux index 72065a3c8..36e5678db 100644 --- a/stdlib/source/lux/tool/compiler/default/evaluation.lux +++ b/stdlib/source/lux/tool/compiler/default/evaluation.lux @@ -2,8 +2,9 @@ [lux #* [abstract [monad (#+ do)]] + [control + ["." try]] [data - ["." error] [text ["%" format (#+ format)]]]] [/// @@ -32,7 +33,7 @@ (do phase.monad [exprA (type.with-type type (analyze exprC))] - (phase.lift (do error.monad + (phase.lift (do try.monad [exprS (|> exprA synthesisP.phase (phase.run synthesis-state))] (phase.run generation-state (do phase.monad diff --git a/stdlib/source/lux/tool/compiler/default/init.lux b/stdlib/source/lux/tool/compiler/default/init.lux index f59a171dd..d24c2828d 100644 --- a/stdlib/source/lux/tool/compiler/default/init.lux +++ b/stdlib/source/lux/tool/compiler/default/init.lux @@ -3,10 +3,10 @@ [abstract ["." monad (#+ do)]] [control + ["." try (#+ Try)] ["ex" exception (#+ exception:)]] [data ["." product] - ["." error (#+ Error)] ["." text ("#@." hash)] [collection ["." list ("#@." functor)] @@ -78,22 +78,22 @@ (def: (reader current-module aliases [cursor offset source-code]) (-> Module Aliases Source (///analysis.Operation Reader)) (function (_ [bundle state]) - (#error.Success [[bundle state] - (//syntax.parse current-module aliases ("lux text size" source-code))]))) + (#try.Success [[bundle state] + (//syntax.parse current-module aliases ("lux text size" source-code))]))) (def: (read source reader) (-> Source Reader (///analysis.Operation [Source Code])) (function (_ [bundle compiler]) (case (reader source) (#.Left [source' error]) - (#error.Failure error) + (#try.Failure error) (#.Right [source' output]) (let [[cursor _] output] - (#error.Success [[bundle (|> compiler - (set@ #.source source') - (set@ #.cursor cursor))] - [source' output]]))))) + (#try.Success [[bundle (|> compiler + (set@ #.source source') + (set@ #.cursor cursor))] + [source' output]]))))) (type: (Operation a) (All [anchor expression statement] @@ -170,13 +170,13 @@ (..reader module aliases source))] (function (_ state) (case (///phase.run' state (..iteration expander reader source pre-buffer)) - (#error.Success [state source&requirements&buffer]) - (#error.Success [state (#.Some source&requirements&buffer)]) + (#try.Success [state source&requirements&buffer]) + (#try.Success [state (#.Some source&requirements&buffer)]) - (#error.Failure error) + (#try.Failure error) (if (ex.match? //syntax.end-of-file error) - (#error.Success [state #.None]) - (ex.with-stack ///.cannot-compile module (#error.Failure error))))))) + (#try.Success [state #.None]) + (ex.with-stack ///.cannot-compile module (#try.Failure error))))))) (def: (default-dependencies prelude input) (-> Module ///.Input (List Module)) @@ -197,7 +197,7 @@ (let [dependencies (default-dependencies prelude input)] {#///.dependencies dependencies #///.process (function (_ state archive) - (do error.monad + (do try.monad [#let [hash (text@hash (get@ #///.code input))] [state [source buffer]] (<| (///phase.run' state) (..begin dependencies hash input)) diff --git a/stdlib/source/lux/tool/compiler/default/platform.lux b/stdlib/source/lux/tool/compiler/default/platform.lux index ab24a52a7..ad82d860b 100644 --- a/stdlib/source/lux/tool/compiler/default/platform.lux +++ b/stdlib/source/lux/tool/compiler/default/platform.lux @@ -3,10 +3,11 @@ [type (#+ :share)] [abstract ["." monad (#+ Monad do)]] + [control + ["." try (#+ Try)]] [data ["." bit] ["." product] - ["." error (#+ Error)] [text ["%" format (#+ format)]] [collection @@ -44,7 +45,7 @@ ## (def: (write-module target-dir file-name module-name module outputs) ## (-> File Text Text Module Outputs (Process Any)) -## (do (error.with io.monad) +## (do (try.with io.monad) ## [_ (monad.map @ (product.uncurry (&io.write target-dir)) ## (dictionary.entries outputs))] ## (&io.write target-dir @@ -65,7 +66,7 @@ <Bundle> (///statement.Bundle anchor expression statement) (-> expression statement) - (! (Error <State+>)))) + (! (Try <State+>)))) (|> platform (get@ #runtime) ///statement.lift-generation @@ -77,13 +78,13 @@ generation-bundle host-statement-bundle program)) - (:: error.functor map product.left) + (:: try.functor map product.left) (:: (get@ #&monad platform) wrap)) ## (case (runtimeT.generate ## (initL.compiler (io.run js.init)) ## (initL.compiler (io.run hostL.init-host)) ## ) - ## ## (#error.Success [state disk-write]) + ## ## (#try.Success [state disk-write]) ## ## (do @ ## ## [_ (&io.prepare-target target) ## ## _ disk-write @@ -92,7 +93,7 @@ ## ## (wrap (|> state ## ## (set@ [#.info #.mode] #.Build)))) - ## (#error.Success [state [runtime-bc function-bc]]) + ## (#try.Success [state [runtime-bc function-bc]]) ## (do @ ## [_ (&io.prepare-target target) ## ## _ (&io.write target (format hostL.runtime-class ".class") runtime-bc) @@ -102,13 +103,13 @@ ## (wrap (|> state ## (set@ [#.info #.mode] #.Build)))) - ## (#error.Failure error) + ## (#try.Failure error) ## (io.fail error)) ) (def: #export (compile partial-host-extension expander platform configuration archive state) (All <type-vars> - (-> Text Expander <Platform> Configuration Archive <State+> (! (Error [Archive <State+>])))) + (-> Text Expander <Platform> Configuration Archive <State+> (! (Try [Archive <State+>])))) (let [monad (get@ #&monad platform) source-module (get@ #cli.module configuration) compiler (:share [anchor expression statement] @@ -119,14 +120,14 @@ (loop [module source-module [archive state] [archive state]] (if (archive.archived? archive module) - (:: monad wrap (#error.Success [archive state])) + (:: monad wrap (#try.Success [archive state])) (let [import! (:share <type-vars> {<Platform> platform} {(-> Module [Archive <State+>] - (! (Error [Archive <State+>]))) + (! (Try [Archive <State+>]))) recur})] - (do (error.with monad) + (do (try.with monad) [input (context.read monad (get@ #&file-system platform) (get@ #cli.sources configuration) @@ -154,7 +155,7 @@ {<Platform> platform} {(-> Archive <State+> (///.Compilation <State+> .Module Any) - (! (Error [Archive <State+>]))) + (! (Try [Archive <State+>]))) recur})]] (case ((get@ #///.process compilation) (case dependencies @@ -166,22 +167,22 @@ (|> (///analysis.set-current-module module) ///statement.lift-analysis (///phase.run' state) - error.assume + try.assume product.left)) archive) - (#error.Success [state more|done]) + (#try.Success [state more|done]) (case more|done (#.Left more) (continue! archive state more) (#.Right [descriptor+document output]) (case (archive.add module descriptor+document archive) - (#error.Success archive) + (#try.Success archive) (wrap [archive state]) - (#error.Failure error) - (:: monad wrap (#error.Failure error)))) + (#try.Failure error) + (:: monad wrap (#try.Failure error)))) - (#error.Failure error) - (:: monad wrap (#error.Failure error))))))))))) + (#try.Failure error) + (:: monad wrap (#try.Failure error))))))))))) ) diff --git a/stdlib/source/lux/tool/compiler/default/syntax.lux b/stdlib/source/lux/tool/compiler/default/syntax.lux index d9a82695b..16a7b4771 100644 --- a/stdlib/source/lux/tool/compiler/default/syntax.lux +++ b/stdlib/source/lux/tool/compiler/default/syntax.lux @@ -34,7 +34,6 @@ [text (#+ Offset)]]] [data ["." maybe] - ["." error (#+ Error)] [number ["." nat] ["." int] diff --git a/stdlib/source/lux/tool/compiler/meta/archive.lux b/stdlib/source/lux/tool/compiler/meta/archive.lux index 9953a7b2f..06323df9c 100644 --- a/stdlib/source/lux/tool/compiler/meta/archive.lux +++ b/stdlib/source/lux/tool/compiler/meta/archive.lux @@ -4,9 +4,9 @@ ["." equivalence (#+ Equivalence)] ["." monad (#+ do)]] [control + ["." try (#+ Try)] ["ex" exception (#+ exception:)]] [data - ["." error (#+ Error)] ["." name] ["." text] [collection @@ -44,24 +44,24 @@ (:abstraction (dictionary.new text.hash))) (def: #export (add module [descriptor document] archive) - (-> Module [Descriptor (Document Any)] Archive (Error Archive)) + (-> Module [Descriptor (Document Any)] Archive (Try Archive)) (case (dictionary.get module (:representation archive)) (#.Some [existing-descriptor existing-document]) (if (is? document existing-document) - (#error.Success archive) + (#try.Success archive) (ex.throw cannot-replace-document [module existing-document document])) #.None - (#error.Success (|> archive - :representation - (dictionary.put module [descriptor document]) - :abstraction)))) + (#try.Success (|> archive + :representation + (dictionary.put module [descriptor document]) + :abstraction)))) (def: #export (find module archive) - (-> Module Archive (Error [Descriptor (Document Any)])) + (-> Module Archive (Try [Descriptor (Document Any)])) (case (dictionary.get module (:representation archive)) (#.Some document) - (#error.Success document) + (#try.Success document) #.None (ex.throw unknown-document [module]))) @@ -69,10 +69,10 @@ (def: #export (archived? archive module) (-> Archive Module Bit) (case (find module archive) - (#error.Success _) + (#try.Success _) yes - (#error.Failure _) + (#try.Failure _) no)) (def: #export archived @@ -80,8 +80,8 @@ (|>> :representation dictionary.keys)) (def: #export (merge additions archive) - (-> Archive Archive (Error Archive)) - (monad.fold error.monad + (-> Archive Archive (Try Archive)) + (monad.fold try.monad (function (_ [module' descriptor+document'] archive') (..add module' descriptor+document' archive')) archive diff --git a/stdlib/source/lux/tool/compiler/meta/archive/document.lux b/stdlib/source/lux/tool/compiler/meta/archive/document.lux index 505170efb..e6d5c0dfe 100644 --- a/stdlib/source/lux/tool/compiler/meta/archive/document.lux +++ b/stdlib/source/lux/tool/compiler/meta/archive/document.lux @@ -1,9 +1,9 @@ (.module: [lux (#- Module) [control + ["." try (#+ Try)] ["ex" exception (#+ exception:)]] [data - ["." error (#+ Error)] [collection ["." dictionary (#+ Dictionary)]]] [type (#+ :share) @@ -24,16 +24,16 @@ #content d} (def: #export (read key document) - (All [d] (-> (Key d) (Document Any) (Error d))) + (All [d] (-> (Key d) (Document Any) (Try d))) (let [[document//signature document//content] (:representation document)] (if (:: signature.equivalence = (key.signature key) document//signature) - (#error.Success (:share [e] - {(Key e) - key} - {e - document//content})) + (#try.Success (:share [e] + {(Key e) + key} + {e + document//content})) (ex.throw invalid-signature [(key.signature key) document//signature])))) diff --git a/stdlib/source/lux/tool/compiler/meta/cache.lux b/stdlib/source/lux/tool/compiler/meta/cache.lux index 382ca7bfd..31cf37b9a 100644 --- a/stdlib/source/lux/tool/compiler/meta/cache.lux +++ b/stdlib/source/lux/tool/compiler/meta/cache.lux @@ -2,12 +2,12 @@ [lux (#- Module) [control ["." monad (#+ Monad do)] + ["." try] ["ex" exception (#+ exception:)] pipe] [data ["." bit ("#;." equivalence)] ["." maybe] - ["." error] ["." product] [format ["." binary (#+ Format)]] @@ -124,7 +124,7 @@ [document' (:: System<m> read (//io/archive.document System<m> root module)) [module' source-code] (//io/context.read System<m> contexts module) #let [current-hash (:: text.hash hash source-code)]] - (case (do error.monad + (case (do try.monad [[signature descriptor content] (binary.read (..document binary) document') #let [[document-hash _file references _state] descriptor] _ (ex.assert mismatched-signature [module (get@ #//archive.signature key) signature] @@ -135,10 +135,10 @@ (n/= current-hash document-hash)) document (//archive.write key signature descriptor content)] (wrap [[module references] document])) - (#error.Success [dependency document]) + (#try.Success [dependency document]) (wrap (#.Some [dependency document])) - (#error.Failure error) + (#try.Failure error) (do @ [_ (un-install System<m> root module)] (wrap #.None))))) diff --git a/stdlib/source/lux/tool/compiler/meta/io/archive.lux b/stdlib/source/lux/tool/compiler/meta/io/archive.lux index bad568cb6..5b33e60a3 100644 --- a/stdlib/source/lux/tool/compiler/meta/io/archive.lux +++ b/stdlib/source/lux/tool/compiler/meta/io/archive.lux @@ -2,9 +2,9 @@ [lux (#- Module) [control monad + ["." try] ["ex" exception (#+ exception:)]] [data - ["." error] ["." text ["%" format (#+ format)]]] [world @@ -52,10 +52,10 @@ (do @ [outcome (:: System<m> try (:: System<m> make-directory document))] (case outcome - (#error.Success output) + (#try.Success output) (wrap output) - (#error.Failure _) + (#try.Failure _) (:: System<m> throw cannot-prepare [archive module])))))) (def: #export (write System<m> root content name) diff --git a/stdlib/source/lux/tool/compiler/meta/io/context.lux b/stdlib/source/lux/tool/compiler/meta/io/context.lux index 7ee9c063d..2e4b355bd 100644 --- a/stdlib/source/lux/tool/compiler/meta/io/context.lux +++ b/stdlib/source/lux/tool/compiler/meta/io/context.lux @@ -4,11 +4,11 @@ [abstract [monad (#+ Monad do)]] [control + ["." try (#+ Try)] ["ex" exception (#+ Exception exception:)] [security ["!" capability]]] [data - ["." error (#+ Error)] ["." text ("#;." hash) ["%" format (#+ format)] ["." encoding]]] @@ -45,7 +45,7 @@ (def: (find-source-file monad system contexts module extension) (All [!] (-> (Monad !) (file.System !) (List Context) Module Extension - (! (Error [Path (File !)])))) + (! (Try [Path (File !)])))) (case contexts #.Nil (:: monad wrap (ex.throw ..cannot-find-module [module])) @@ -55,36 +55,36 @@ [#let [path (format (..path system context module) extension)] file (!.use (:: system file) path)] (case file - (#error.Success file) - (wrap (#error.Success [path file])) + (#try.Success file) + (wrap (#try.Success [path file])) - (#error.Failure error) + (#try.Failure _) (find-source-file monad system contexts' module extension))))) (def: #export (find-any-source-file monad system contexts partial-host-extension module) (All [!] (-> (Monad !) (file.System !) (List Context) Text Module - (! (Error [Path (File !)])))) + (! (Try [Path (File !)])))) (let [full-host-extension (format partial-host-extension lux-extension)] (do monad [outcome (find-source-file monad system contexts module full-host-extension)] (case outcome - (#error.Success output) + (#try.Success output) (wrap outcome) - (#error.Failure error) + (#try.Failure _) (find-source-file monad system contexts module ..lux-extension))))) (def: #export (read monad system contexts partial-host-extension module) (All [!] (-> (Monad !) (file.System !) (List Context) Text Module - (! (Error Input)))) - (do (error.with monad) + (! (Try Input)))) + (do (try.with monad) [## TODO: Get rid of both ":share"s ASAP path,file (:share [!] {(Monad !) monad} - {(! (Error [Path (File !)])) + {(! (Try [Path (File !)])) (find-any-source-file monad system contexts partial-host-extension module)}) #let [[path file] (:share [!] {(Monad !) @@ -93,11 +93,11 @@ path,file})] binary (!.use (:: file content) [])] (case (encoding.from-utf8 binary) - (#error.Success code) + (#try.Success code) (wrap {#////.module module #////.file path #////.hash (text;hash code) #////.code code}) - (#error.Failure _) + (#try.Failure _) (:: monad wrap (ex.throw ..cannot-read-module [module]))))) diff --git a/stdlib/source/lux/tool/compiler/phase.lux b/stdlib/source/lux/tool/compiler/phase.lux index 7107ac9da..596d94f6b 100644 --- a/stdlib/source/lux/tool/compiler/phase.lux +++ b/stdlib/source/lux/tool/compiler/phase.lux @@ -4,13 +4,13 @@ [monad (#+ Monad do)]] [control ["." state] + ["." try (#+ Try) ("#@." functor)] ["ex" exception (#+ Exception exception:)] ["." io] [parser ["s" code]]] [data ["." product] - ["." error (#+ Error) ("#@." functor)] ["." text ["%" format (#+ format)]]] [time @@ -20,38 +20,38 @@ [syntax (#+ syntax:)]]]) (type: #export (Operation s o) - (state.State' Error s o)) + (state.State' Try s o)) (def: #export monad (All [s] (Monad (Operation s))) - (state.with error.monad)) + (state.with try.monad)) (type: #export (Phase s i o) (-> i (Operation s o))) (def: #export (run' state operation) (All [s o] - (-> s (Operation s o) (Error [s o]))) + (-> s (Operation s o) (Try [s o]))) (operation state)) (def: #export (run state operation) (All [s o] - (-> s (Operation s o) (Error o))) + (-> s (Operation s o) (Try o))) (|> state operation - (:: error.monad map product.right))) + (:: try.monad map product.right))) (def: #export get-state (All [s o] (Operation s s)) (function (_ state) - (#error.Success [state state]))) + (#try.Success [state state]))) (def: #export (set-state state) (All [s o] (-> s (Operation s Any))) (function (_ _) - (#error.Success [state []]))) + (#try.Success [state []]))) (def: #export (sub [get set] operation) (All [s s' o] @@ -59,22 +59,22 @@ (Operation s' o) (Operation s o))) (function (_ state) - (do error.monad + (do try.monad [[state' output] (operation (get state))] (wrap [(set state' state) output])))) (def: #export fail (-> Text Operation) - (|>> error.fail (state.lift error.monad))) + (|>> try.fail (state.lift try.monad))) (def: #export (throw exception parameters) (All [e] (-> (Exception e) e Operation)) (..fail (ex.construct exception parameters))) (def: #export (lift error) - (All [s a] (-> (Error a) (Operation s a))) + (All [s a] (-> (Try a) (Operation s a))) (function (_ state) - (error@map (|>> [state]) error))) + (try@map (|>> [state]) error))) (syntax: #export (assert exception message test) (wrap (list (` (if (~ test) @@ -84,7 +84,7 @@ (def: #export identity (All [s a] (Phase s a a)) (function (_ input state) - (#error.Success [state input]))) + (#try.Success [state input]))) (def: #export (compose pre post) (All [s0 s1 i t o] @@ -92,7 +92,7 @@ (Phase s1 t o) (Phase [s0 s1] i o))) (function (_ input [pre/state post/state]) - (do error.monad + (do try.monad [[pre/state' temp] (pre input pre/state) [post/state' output] (post temp post/state)] (wrap [[pre/state' post/state'] output])))) diff --git a/stdlib/source/lux/tool/compiler/phase/analysis.lux b/stdlib/source/lux/tool/compiler/phase/analysis.lux index 9281046c1..fbdb18f16 100644 --- a/stdlib/source/lux/tool/compiler/phase/analysis.lux +++ b/stdlib/source/lux/tool/compiler/phase/analysis.lux @@ -5,7 +5,6 @@ [control ["ex" exception (#+ exception:)]] [data - ["." error] [text ["%" format (#+ format)]]] ["." macro]] diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/case.lux b/stdlib/source/lux/tool/compiler/phase/analysis/case.lux index 85be37a90..dd45ab734 100644 --- a/stdlib/source/lux/tool/compiler/phase/analysis/case.lux +++ b/stdlib/source/lux/tool/compiler/phase/analysis/case.lux @@ -3,10 +3,10 @@ [abstract ["." monad (#+ do)]] [control + ["." try] ["ex" exception (#+ exception:)]] [data ["." product] - ["." error] ["." maybe] [text ["%" format (#+ format)]] @@ -304,12 +304,12 @@ branchesT) outputHC (|> outputH product.left /coverage.determine) outputTC (monad.map @ (|>> product.left /coverage.determine) outputT) - _ (.case (monad.fold error.monad /coverage.merge outputHC outputTC) - (#error.Success coverage) + _ (.case (monad.fold try.monad /coverage.merge outputHC outputTC) + (#try.Success coverage) (///.assert non-exhaustive-pattern-matching [inputC branches coverage] (/coverage.exhaustive? coverage)) - (#error.Failure error) + (#try.Failure error) (/.fail error))] (wrap (#/.Case inputA [outputH outputT]))) diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/case/coverage.lux b/stdlib/source/lux/tool/compiler/phase/analysis/case/coverage.lux index 067ce0972..af43a0e53 100644 --- a/stdlib/source/lux/tool/compiler/phase/analysis/case/coverage.lux +++ b/stdlib/source/lux/tool/compiler/phase/analysis/case/coverage.lux @@ -4,10 +4,10 @@ equivalence ["." monad (#+ do)]] [control + ["." try (#+ Try) ("#@." monad)] ["ex" exception (#+ exception:)]] [data ["." bit ("#@." equivalence)] - ["." error (#+ Error) ("#@." monad)] ["." maybe] [number ["." nat]] @@ -214,15 +214,15 @@ ## pattern-matching expression is exhaustive and whether it contains ## redundant patterns. (def: #export (merge addition so-far) - (-> Coverage Coverage (Error Coverage)) + (-> Coverage Coverage (Try Coverage)) (case [addition so-far] [#Partial #Partial] - (error@wrap #Partial) + (try@wrap #Partial) ## 2 bit coverages are exhaustive if they complement one another. (^multi [(#Bit sideA) (#Bit sideSF)] (xor sideA sideSF)) - (error@wrap #Exhaustive) + (try@wrap #Exhaustive) [(#Variant allA casesA) (#Variant allSF casesSF)] (let [addition-cases (cases allSF) @@ -236,7 +236,7 @@ (ex.throw redundant-pattern [so-far addition]) ## else - (do error.monad + (do try.monad [casesM (monad.fold @ (function (_ [tagA coverageA] casesSF') (case (dictionary.get tagA casesSF') @@ -266,7 +266,7 @@ (case [(coverage/= leftSF leftA) (coverage/= rightSF rightA)] ## Same prefix [#1 #0] - (do error.monad + (do try.monad [rightM (merge rightA rightSF)] (if (exhaustive? rightM) ## If all that follows is exhaustive, then it can be safely dropped @@ -277,13 +277,13 @@ ## Same suffix [#0 #1] - (do error.monad + (do try.monad [leftM (merge leftA leftSF)] (wrap (#Seq leftM rightA))) ## The 2 sequences cannot possibly be merged. [#0 #0] - (error@wrap (#Alt so-far addition)) + (try@wrap (#Alt so-far addition)) ## There is nothing the addition adds to the coverage. [#1 #1] @@ -295,7 +295,7 @@ ## The addition completes the coverage. [#Exhaustive _] - (error@wrap #Exhaustive) + (try@wrap #Exhaustive) ## The left part will always match, so the addition is redundant. (^multi [(#Seq left right) single] @@ -305,7 +305,7 @@ ## The right part is not necessary, since it can always match the left. (^multi [single (#Seq left right)] (coverage/= left single)) - (error@wrap single) + (try@wrap single) ## When merging a new coverage against one based on Alt, it may be ## that one of the many coverages in the Alt is complementary to @@ -317,10 +317,10 @@ ## This process must be repeated until no further productive ## merges can be done. [_ (#Alt leftS rightS)] - (do error.monad + (do try.monad [#let [fuse-once (: (-> Coverage (List Coverage) - (Error [(Maybe Coverage) - (List Coverage)])) + (Try [(Maybe Coverage) + (List Coverage)])) (function (_ coverageA possibilitiesSF) (loop [altsSF possibilitiesSF] (case altsSF @@ -329,7 +329,7 @@ (#.Cons altSF altsSF') (case (merge coverageA altSF) - (#error.Success altMSF) + (#try.Success altMSF) (case altMSF (#Alt _) (do @ @@ -339,8 +339,8 @@ _ (wrap [(#.Some altMSF) altsSF'])) - (#error.Failure error) - (error.fail error)) + (#try.Failure error) + (try.fail error)) ))))] [successA possibilitiesSF] (fuse-once addition (flatten-alt so-far))] (loop [successA successA @@ -366,4 +366,4 @@ ## The addition cannot possibly improve the coverage. (ex.throw redundant-pattern [so-far addition]) ## There are now 2 alternative paths. - (error@wrap (#Alt so-far addition))))) + (try@wrap (#Alt so-far addition))))) diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/module.lux b/stdlib/source/lux/tool/compiler/phase/analysis/module.lux index c6280e4b3..bb1094b2a 100644 --- a/stdlib/source/lux/tool/compiler/phase/analysis/module.lux +++ b/stdlib/source/lux/tool/compiler/phase/analysis/module.lux @@ -4,11 +4,11 @@ ["." monad (#+ do)]] [control pipe + ["." try] ["ex" exception (#+ exception:)]] [data ["." text ("#@." equivalence) ["%" format (#+ format)]] - ["." error] [collection ["." list ("#@." fold functor)] [dictionary @@ -72,10 +72,10 @@ (case (get@ #.module-annotations self) #.None (function (_ state) - (#error.Success [(update@ #.modules - (plist.put self-name (set@ #.module-annotations (#.Some annotations) self)) - state) - []])) + (#try.Success [(update@ #.modules + (plist.put self-name (set@ #.module-annotations (#.Some annotations) self)) + state) + []])) (#.Some old) (/.throw' cannot-set-module-annotations-more-than-once [self-name old annotations]))))) @@ -86,14 +86,14 @@ (do ///.monad [self-name macro.current-module-name] (function (_ state) - (#error.Success [(update@ #.modules - (plist.update self-name (update@ #.imports (function (_ current) - (if (list.any? (text@= module) - current) - current - (#.Cons module current))))) - state) - []]))))) + (#try.Success [(update@ #.modules + (plist.update self-name (update@ #.imports (function (_ current) + (if (list.any? (text@= module) + current) + current + (#.Cons module current))))) + state) + []]))))) (def: #export (alias alias module) (-> Text Text (Operation Any)) @@ -101,11 +101,11 @@ (do ///.monad [self-name macro.current-module-name] (function (_ state) - (#error.Success [(update@ #.modules - (plist.update self-name (update@ #.module-aliases (: (-> (List [Text Text]) (List [Text Text])) - (|>> (#.Cons [alias module]))))) - state) - []]))))) + (#try.Success [(update@ #.modules + (plist.update self-name (update@ #.module-aliases (: (-> (List [Text Text]) (List [Text Text])) + (|>> (#.Cons [alias module]))))) + state) + []]))))) (def: #export (exists? module) (-> Text (Operation Bit)) @@ -115,7 +115,7 @@ (get@ #.modules) (plist.get module) (case> (#.Some _) #1 #.None #0) - [state] #error.Success)))) + [state] #try.Success)))) (def: #export (define name definition) (-> Text Global (Operation Any)) @@ -126,14 +126,14 @@ (function (_ state) (case (plist.get name (get@ #.definitions self)) #.None - (#error.Success [(update@ #.modules - (plist.put self-name - (update@ #.definitions - (: (-> (List [Text Global]) (List [Text Global])) - (|>> (#.Cons [name definition]))) - self)) - state) - []]) + (#try.Success [(update@ #.modules + (plist.put self-name + (update@ #.definitions + (: (-> (List [Text Global]) (List [Text Global])) + (|>> (#.Cons [name definition]))) + self)) + state) + []]) (#.Some already-existing) ((/.throw' cannot-define-more-than-once [self-name name]) state)))))) @@ -143,10 +143,10 @@ (///extension.lift (function (_ state) (let [module (new hash)] - (#error.Success [(update@ #.modules - (plist.put name module) - state) - []]))))) + (#try.Success [(update@ #.modules + (plist.put name module) + state) + []]))))) (def: #export (with-module hash name action) (All [a] (-> Nat Text (Operation a) (Operation [Module a]))) @@ -168,10 +168,10 @@ #.Active #1 _ #0)] (if active? - (#error.Success [(update@ #.modules - (plist.put module-name (set@ #.module-state <tag> module)) - state) - []]) + (#try.Success [(update@ #.modules + (plist.put module-name (set@ #.module-state <tag> module)) + state) + []]) ((/.throw' can-only-change-state-of-active-module [module-name <tag>]) state))) @@ -184,10 +184,10 @@ (function (_ state) (case (|> state (get@ #.modules) (plist.get module-name)) (#.Some module) - (#error.Success [state - (case (get@ #.module-state module) - <tag> #1 - _ #0)]) + (#try.Success [state + (case (get@ #.module-state module) + <tag> #1 + _ #0)]) #.None ((/.throw' unknown-module module-name) state)))))] @@ -204,7 +204,7 @@ (function (_ state) (case (|> state (get@ #.modules) (plist.get module-name)) (#.Some module) - (#error.Success [state (get@ <tag> module)]) + (#try.Success [state (get@ <tag> module)]) #.None ((/.throw' unknown-module module-name) state)))))] @@ -247,15 +247,15 @@ (case (|> state (get@ #.modules) (plist.get self-name)) (#.Some module) (let [namespaced-tags (list@map (|>> [self-name]) tags)] - (#error.Success [(update@ #.modules - (plist.update self-name - (|>> (update@ #.tags (function (_ tag-bindings) - (list@fold (function (_ [idx tag] table) - (plist.put tag [idx namespaced-tags exported? type] table)) - tag-bindings - (list.enumerate tags)))) - (update@ #.types (plist.put type-name [namespaced-tags exported? type])))) - state) - []])) + (#try.Success [(update@ #.modules + (plist.update self-name + (|>> (update@ #.tags (function (_ tag-bindings) + (list@fold (function (_ [idx tag] table) + (plist.put tag [idx namespaced-tags exported? type] table)) + tag-bindings + (list.enumerate tags)))) + (update@ #.types (plist.put type-name [namespaced-tags exported? type])))) + state) + []])) #.None ((/.throw' unknown-module self-name) state)))))) diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/scope.lux b/stdlib/source/lux/tool/compiler/phase/analysis/scope.lux index 104001da9..e5d145a54 100644 --- a/stdlib/source/lux/tool/compiler/phase/analysis/scope.lux +++ b/stdlib/source/lux/tool/compiler/phase/analysis/scope.lux @@ -3,12 +3,12 @@ [abstract monad] [control + ["e" try] ["ex" exception (#+ exception:)]] [data ["." text ("#;." equivalence)] ["." maybe ("#;." monad)] ["." product] - ["e" error] [collection ["." list ("#;." functor fold monoid)] [dictionary diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/structure.lux b/stdlib/source/lux/tool/compiler/phase/analysis/structure.lux index a630a8fab..eeb2cf9e0 100644 --- a/stdlib/source/lux/tool/compiler/phase/analysis/structure.lux +++ b/stdlib/source/lux/tool/compiler/phase/analysis/structure.lux @@ -9,7 +9,6 @@ ["." name] ["." product] ["." maybe] - ["." error] [number ["." nat]] [text diff --git a/stdlib/source/lux/tool/compiler/phase/analysis/type.lux b/stdlib/source/lux/tool/compiler/phase/analysis/type.lux index d7ebbe2a3..20b313381 100644 --- a/stdlib/source/lux/tool/compiler/phase/analysis/type.lux +++ b/stdlib/source/lux/tool/compiler/phase/analysis/type.lux @@ -3,9 +3,8 @@ [abstract [monad (#+ do)]] [control - ["." function]] - [data - ["." error]] + ["." function] + ["." try]] [type ["." check (#+ Check)]] ["." macro]] @@ -23,11 +22,11 @@ (All [a] (-> (Check a) (Operation a))) (function (_ (^@ stateE [bundle state])) (case (action (get@ #.type-context state)) - (#error.Success [context' output]) - (#error.Success [[bundle (set@ #.type-context context' state)] - output]) + (#try.Success [context' output]) + (#try.Success [[bundle (set@ #.type-context context' state)] + output]) - (#error.Failure error) + (#try.Failure error) ((/.fail error) stateE)))) (def: #export with-fresh-env diff --git a/stdlib/source/lux/tool/compiler/phase/extension.lux b/stdlib/source/lux/tool/compiler/phase/extension.lux index 4b00c946f..a0564cedd 100644 --- a/stdlib/source/lux/tool/compiler/phase/extension.lux +++ b/stdlib/source/lux/tool/compiler/phase/extension.lux @@ -4,9 +4,9 @@ [monad (#+ do)]] [control ["." function] + ["." try (#+ Try)] ["." exception (#+ exception:)]] [data - ["." error (#+ Error)] ["." text ("#@." order) ["%" format (#+ Format format)]] [collection @@ -67,8 +67,8 @@ (function (_ [bundle state]) (case (dictionary.get name bundle) #.None - (#error.Success [[(dictionary.put name handler bundle) state] - []]) + (#try.Success [[(dictionary.put name handler bundle) state] + []]) _ (exception.throw cannot-overwrite name)))) @@ -93,11 +93,11 @@ (function (_ [bundle state]) (let [old (get state)] (case (operation [bundle (set (transform old) state)]) - (#error.Success [[bundle' state'] output]) - (#error.Success [[bundle' (set old state')] output]) + (#try.Success [[bundle' state'] output]) + (#try.Success [[bundle' (set old state')] output]) - (#error.Failure error) - (#error.Failure error)))))) + (#try.Failure error) + (#try.Failure error)))))) (def: #export (temporary transform) (All [s i o v] @@ -106,11 +106,11 @@ (function (_ operation) (function (_ [bundle state]) (case (operation [bundle (transform state)]) - (#error.Success [[bundle' state'] output]) - (#error.Success [[bundle' state] output]) + (#try.Success [[bundle' state'] output]) + (#try.Success [[bundle' state] output]) - (#error.Failure error) - (#error.Failure error))))) + (#try.Failure error) + (#try.Failure error))))) (def: #export (with-state state) (All [s i o v] @@ -121,13 +121,13 @@ (All [s i o v] (-> (-> s v) (Operation s i o v))) (function (_ [bundle state]) - (#error.Success [[bundle state] (get state)]))) + (#try.Success [[bundle state] (get state)]))) (def: #export (update transform) (All [s i o] (-> (-> s s) (Operation s i o Any))) (function (_ [bundle state]) - (#error.Success [[bundle (transform state)] []]))) + (#try.Success [[bundle (transform state)] []]))) (def: #export (lift action) (All [s i o v] @@ -135,8 +135,8 @@ (//.Operation [(Bundle s i o) s] v))) (function (_ [bundle state]) (case (action state) - (#error.Success [state' output]) - (#error.Success [[bundle state'] output]) + (#try.Success [state' output]) + (#try.Success [[bundle state'] output]) - (#error.Failure error) - (#error.Failure error)))) + (#try.Failure error) + (#try.Failure error)))) diff --git a/stdlib/source/lux/tool/compiler/phase/extension/analysis/jvm.lux b/stdlib/source/lux/tool/compiler/phase/extension/analysis/jvm.lux index fa31254c8..3acecec11 100644 --- a/stdlib/source/lux/tool/compiler/phase/extension/analysis/jvm.lux +++ b/stdlib/source/lux/tool/compiler/phase/extension/analysis/jvm.lux @@ -5,13 +5,13 @@ [abstract ["." monad (#+ do)]] [control + ["." try (#+ Try) ("#@." monad)] ["<>" parser ["<c>" code (#+ Parser)] ["<t>" text]] ["." exception (#+ exception:)] pipe] [data - ["." error (#+ Error) ("#@." monad)] ["." maybe] ["." product] ["." text ("#@." equivalence) @@ -829,7 +829,7 @@ (function (_ extension-name analyse [class field]) (do ////.monad [[final? fieldJT] (////.lift - (do error.monad + (do try.monad [class (reflection!.load class)] (reflection!.static-field field class))) fieldT (reflection-type luxT.fresh fieldJT) @@ -847,7 +847,7 @@ (do ////.monad [_ (typeA.infer Any) [final? fieldJT] (////.lift - (do error.monad + (do try.monad [class (reflection!.load class)] (reflection!.static-field field class))) fieldT (reflection-type luxT.fresh fieldJT) @@ -869,7 +869,7 @@ [[objectT objectA] (typeA.with-inference (analyse objectC)) [mapping fieldJT] (////.lift - (do error.monad + (do try.monad [class (reflection!.load class) [final? fieldJT] (reflection!.virtual-field field class) mapping (reflection!.correspond class objectT)] @@ -892,7 +892,7 @@ (analyse objectC)) _ (typeA.infer objectT) [final? mapping fieldJT] (////.lift - (do error.monad + (do try.monad [class (reflection!.load class) [final? fieldJT] (reflection!.virtual-field field class) mapping (reflection!.correspond class objectT)] @@ -921,8 +921,8 @@ (do ////.monad [parameters (|> (java/lang/reflect/Method::getGenericParameterTypes method) array.to-list - (monad.map error.monad reflection!.type) - (:: error.monad map (list@map jvm.descriptor)) + (monad.map try.monad reflection!.type) + (:: try.monad map (list@map jvm.descriptor)) ////.lift) #let [modifiers (java/lang/reflect/Method::getModifiers method) correct-class? (java/lang/Object::equals class (java/lang/reflect/Method::getDeclaringClass method)) @@ -958,8 +958,8 @@ (do ////.monad [parameters (|> (java/lang/reflect/Constructor::getGenericParameterTypes constructor) array.to-list - (monad.map error.monad reflection!.type) - (:: error.monad map (list@map jvm.descriptor)) + (monad.map try.monad reflection!.type) + (:: try.monad map (list@map jvm.descriptor)) ////.lift)] (wrap (and (java/lang/Object::equals class (java/lang/reflect/Constructor::getDeclaringClass constructor)) (n/= (list.size arg-classes) (list.size parameters)) @@ -1401,13 +1401,13 @@ (template [<name> <filter>] [(def: <name> (-> (java/lang/Class java/lang/Object) - (Error (List [Text Method]))) + (Try (List [Text Method]))) (|>> java/lang/Class::getDeclaredMethods array.to-list <filter> - (monad.map error.monad + (monad.map try.monad (function (_ method) - (do error.monad + (do try.monad [inputs (|> (java/lang/reflect/Method::getGenericParameterTypes method) array.to-list (monad.map @ reflection!.type)) @@ -1428,11 +1428,11 @@ (template [<name> <methods>] [(def: <name> - (-> (List Class) (Error (List [Text Method]))) - (|>> (monad.map error.monad (|>> product.left reflection!.load)) - (error@map (monad.map error.monad <methods>)) - error@join - (error@map list@join)))] + (-> (List Class) (Try (List [Text Method]))) + (|>> (monad.map try.monad (|>> product.left reflection!.load)) + (try@map (monad.map try.monad <methods>)) + try@join + (try@map list@join)))] [all-abstract-methods ..abstract-methods] [all-methods ..methods] diff --git a/stdlib/source/lux/tool/compiler/phase/extension/analysis/lux.lux b/stdlib/source/lux/tool/compiler/phase/extension/analysis/lux.lux index 2086a0fea..efd917bd2 100644 --- a/stdlib/source/lux/tool/compiler/phase/extension/analysis/lux.lux +++ b/stdlib/source/lux/tool/compiler/phase/extension/analysis/lux.lux @@ -4,12 +4,12 @@ ["." monad (#+ do)]] [control [io (#+ IO)] + ["." try] ["." exception (#+ exception:)] ["<>" parser ["<c>" code (#+ Parser)]]] [data ["." maybe] - ["." error] ["." text ["%" format (#+ format)]] [collection @@ -37,10 +37,10 @@ Handler)) (function (_ extension-name analyse args) (case (<c>.run syntax args) - (#error.Success inputs) + (#try.Success inputs) (handler extension-name analyse inputs) - (#error.Failure error) + (#try.Failure _) (/////analysis.throw ///.invalid-syntax [extension-name %.code args])))) (def: (simple inputsT+ outputT) diff --git a/stdlib/source/lux/tool/compiler/phase/extension/statement/lux.lux b/stdlib/source/lux/tool/compiler/phase/extension/statement/lux.lux index e4cf0140e..56067c845 100644 --- a/stdlib/source/lux/tool/compiler/phase/extension/statement/lux.lux +++ b/stdlib/source/lux/tool/compiler/phase/extension/statement/lux.lux @@ -4,13 +4,13 @@ ["." monad (#+ do)]] [control [io (#+ IO)] + ["." try] ["." exception (#+ exception:)] ["p" parser ["s" code (#+ Parser)]]] [data ["." product] ["." maybe] - ["." error] [text ["%" format (#+ format)]] [collection @@ -46,10 +46,10 @@ (Handler anchor expression statement))) (function (_ extension-name phase inputs) (case (s.run syntax inputs) - (#error.Success inputs) + (#try.Success inputs) (handler extension-name phase inputs) - (#error.Failure error) + (#try.Failure error) (////.throw ///.invalid-syntax [extension-name %.code inputs])))) ## TODO: Inline "evaluate!'" into "evaluate!" ASAP diff --git a/stdlib/source/lux/tool/compiler/phase/generation.lux b/stdlib/source/lux/tool/compiler/phase/generation.lux index 93dc97518..aa7d09d66 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation.lux @@ -3,10 +3,10 @@ [abstract [monad (#+ do)]] [control + ["." try (#+ Try)] ["." exception (#+ exception:)]] [data ["." product] - ["." error (#+ Error)] ["." name ("#@." equivalence)] ["." text ["%" format (#+ format)]] @@ -60,11 +60,11 @@ #inner-functions Nat}) (signature: #export (Host expression statement) - (: (-> Text expression (Error Any)) + (: (-> Text expression (Try Any)) evaluate!) - (: (-> Text statement (Error Any)) + (: (-> Text statement (Try Any)) execute!) - (: (-> Name expression (Error [Text Any statement])) + (: (-> Name expression (Try [Text Any statement])) define!)) (type: #export (Buffer statement) (Row [Name statement])) @@ -111,12 +111,12 @@ (let [[old-scope old-inner] (get@ #context state) new-scope (format old-scope "c" (%.nat old-inner))] (case (expr [bundle (set@ #context [new-scope 0] state)]) - (#error.Success [[bundle' state'] output]) - (#error.Success [[bundle' (set@ #context [old-scope (inc old-inner)] state')] - [new-scope output]]) + (#try.Success [[bundle' state'] output]) + (#try.Success [[bundle' (set@ #context [old-scope (inc old-inner)] state')] + [new-scope output]]) - (#error.Failure error) - (#error.Failure error))))) + (#try.Failure error) + (#try.Failure error))))) (def: #export context (All [anchor expression statement] @@ -136,12 +136,12 @@ (function (_ body) (function (_ [bundle state]) (case (body [bundle (set@ <tag> (#.Some <with-value>) state)]) - (#error.Success [[bundle' state'] output]) - (#error.Success [[bundle' (set@ <tag> (get@ <tag> state) state')] - output]) + (#try.Success [[bundle' state'] output]) + (#try.Success [[bundle' (set@ <tag> (get@ <tag> state) state')] + output]) - (#error.Failure error) - (#error.Failure error))))) + (#try.Failure error) + (#try.Failure error))))) (def: #export <get> (All [anchor expression statement] @@ -149,7 +149,7 @@ (function (_ (^@ stateE [bundle state])) (case (get@ <tag> state) (#.Some output) - (#error.Success [stateE output]) + (#try.Success [stateE output]) #.None (exception.throw <exception> [])))) @@ -158,8 +158,8 @@ (All [anchor expression statement] (-> <get-type> (Operation anchor expression statement Any))) (function (_ [bundle state]) - (#error.Success [[bundle (set@ <tag> (#.Some value) state)] - []])))] + (#try.Success [[bundle (set@ <tag> (#.Some value) state)] + []])))] [#anchor (with-anchor anchor) @@ -200,10 +200,10 @@ (-> Text <inputT> (Operation anchor expression statement Any))) (function (_ (^@ state+ [bundle state])) (case (:: (get@ #host state) <name> label code) - (#error.Success output) - (#error.Success [state+ output]) + (#try.Success output) + (#try.Success [state+ output]) - (#error.Failure error) + (#try.Failure error) (exception.throw cannot-interpret error))))] [evaluate! expression] @@ -215,10 +215,10 @@ (-> Name expression (Operation anchor expression statement [Text Any statement]))) (function (_ (^@ stateE [bundle state])) (case (:: (get@ #host state) define! name code) - (#error.Success output) - (#error.Success [stateE output]) + (#try.Success output) + (#try.Success [stateE output]) - (#error.Failure error) + (#try.Failure error) (exception.throw cannot-interpret error)))) (def: #export (save! execute? name code) @@ -253,7 +253,7 @@ (let [cache (get@ #name-cache state)] (case (dictionary.get lux-name cache) (#.Some host-name) - (#error.Success [stateE host-name]) + (#try.Success [stateE host-name]) #.None (exception.throw unknown-lux-name [lux-name cache]))))) @@ -265,11 +265,11 @@ (let [cache (get@ #name-cache state)] (case (dictionary.get lux-name cache) #.None - (#error.Success [[bundle - (update@ #name-cache - (dictionary.put lux-name host-name) - state)] - []]) + (#try.Success [[bundle + (update@ #name-cache + (dictionary.put lux-name host-name) + state)] + []]) (#.Some old-host-name) (exception.throw cannot-overwrite-lux-name [lux-name old-host-name host-name]))))) diff --git a/stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux index f2d22f57b..9baf594da 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/js/extension/common.lux @@ -4,11 +4,11 @@ [abstract ["." monad (#+ do)]] [control + ["." try] ["<>" parser ["<s>" synthesis (#+ Parser)]]] [data ["." product] - ["." error] [collection ["." list ("#@." functor)] ["." dictionary]]] @@ -33,10 +33,10 @@ Handler)) (function (_ extension-name phase input) (case (<s>.run input parser) - (#error.Success input') + (#try.Success input') (handler extension-name phase input') - (#error.Failure error) + (#try.Failure error) (/////.throw extension.invalid-syntax [extension-name %synthesis input])))) ## [Procedures] diff --git a/stdlib/source/lux/tool/compiler/phase/generation/js/extension/host.lux b/stdlib/source/lux/tool/compiler/phase/generation/js/extension/host.lux index 423f0a58d..c44e1bdff 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/js/extension/host.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/js/extension/host.lux @@ -7,7 +7,6 @@ ["<>" parser ["<s>" synthesis (#+ Parser)]]] [data - ["." error] [collection ["." dictionary]]] [target diff --git a/stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/common.lux b/stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/common.lux index 42c1d196d..e23692e88 100644 --- a/stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/common.lux +++ b/stdlib/source/lux/tool/compiler/phase/generation/scheme/extension/common.lux @@ -8,7 +8,6 @@ [parser ["s" code]]] [data - ["e" error] ["." product] ["." text] [number (#+ hex)] diff --git a/stdlib/source/lux/tool/compiler/phase/macro.lux b/stdlib/source/lux/tool/compiler/phase/macro.lux index 10d3cd332..db384c727 100644 --- a/stdlib/source/lux/tool/compiler/phase/macro.lux +++ b/stdlib/source/lux/tool/compiler/phase/macro.lux @@ -3,9 +3,9 @@ [abstract [monad (#+ do)]] [control + ["." try (#+ Try)] ["." exception (#+ exception:)]] [data - ["." error (#+ Error)] ["." text ["%" format (#+ format)]] [collection @@ -27,18 +27,18 @@ ["Outputs" (exception.enumerate %.code outputs)])) (type: #export Expander - (-> Macro (List Code) Lux (Error (Error [Lux (List Code)])))) + (-> Macro (List Code) Lux (Try (Try [Lux (List Code)])))) (def: #export (expand expander name macro inputs) (-> Expander Name Macro (List Code) (Meta (List Code))) (function (_ state) - (do error.monad + (do try.monad [output (expander macro inputs state)] (case output - (#error.Success output) - (#error.Success output) + (#try.Success output) + (#try.Success output) - (#error.Failure error) + (#try.Failure error) ((//.throw expansion-failed [name inputs error]) state))))) (def: #export (expand-one expander name macro inputs) diff --git a/stdlib/source/lux/tool/compiler/phase/synthesis.lux b/stdlib/source/lux/tool/compiler/phase/synthesis.lux index 1b92abf97..45372e46b 100644 --- a/stdlib/source/lux/tool/compiler/phase/synthesis.lux +++ b/stdlib/source/lux/tool/compiler/phase/synthesis.lux @@ -3,10 +3,10 @@ [abstract ["." monad (#+ do)]] [control - [pipe (#+ case>)]] + [pipe (#+ case>)] + ["." try]] [data ["." maybe] - ["." error] [collection ["." list ("#;." functor)] ["." dictionary (#+ Dictionary)]]]] @@ -77,10 +77,10 @@ (function (_ state) (|> (//extension.apply phase [name args]) (//.run' state) - (case> (#error.Success output) - (#error.Success output) + (case> (#try.Success output) + (#try.Success output) - (#error.Failure error) + (#try.Failure _) (<| (//.run' state) (do //.monad [argsS+ (monad.map @ phase args)] diff --git a/stdlib/source/lux/tool/interpreter.lux b/stdlib/source/lux/tool/interpreter.lux index b836e4139..44f14f0ab 100644 --- a/stdlib/source/lux/tool/interpreter.lux +++ b/stdlib/source/lux/tool/interpreter.lux @@ -2,9 +2,9 @@ [lux #* [control [monad (#+ Monad do)] + ["." try (#+ Try)] ["ex" exception (#+ exception:)]] [data - ["." error (#+ Error)] ["." text ("#;." equivalence) ["%" format (#+ format)]]] [type (#+ :share) @@ -129,10 +129,10 @@ state} {<Interpretation> (interpret-statement code)})) - (#error.Success [state' output]) - (#error.Success [state' output]) + (#try.Success [state' output]) + (#try.Success [state' output]) - (#error.Failure error) + (#try.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.Failure error))))) + (#try.Failure error))))) ) (def: (execute configuration code) @@ -164,8 +164,8 @@ (with-expansions [<Context> (as-is (Context anchor expression statement))] (def: (read-eval-print context) (All [anchor expression statement] - (-> <Context> (Error [<Context> Text]))) - (do error.monad + (-> <Context> (Try [<Context> Text]))) + (do try.monad [#let [[_where _offset _code] (get@ #source context)] [source' input] (syntax.parse ..module syntax.no-aliases (text.size _code) (get@ #source context)) [state' representation] (let [## TODO: Simplify ASAP @@ -208,12 +208,12 @@ (text;= ..exit-command line)) (:: Console<!> write ..farewell-message) (case (read-eval-print (update@ #source (add-line line) context)) - (#error.Success [context' representation]) + (#try.Success [context' representation]) (do @ [_ (:: Console<!> write representation)] (recur context' #0)) - (#error.Failure error) + (#try.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/tool/mediator.lux b/stdlib/source/lux/tool/mediator.lux index 4481b6e2e..5beb217e0 100644 --- a/stdlib/source/lux/tool/mediator.lux +++ b/stdlib/source/lux/tool/mediator.lux @@ -1,7 +1,5 @@ (.module: [lux (#- Source Module) - [data - ["." error (#+ Error)]] [world ["." binary (#+ Binary)] ["." file (#+ File)]]] diff --git a/stdlib/source/lux/tool/mediator/parallelism.lux b/stdlib/source/lux/tool/mediator/parallelism.lux index c45c1aeb5..10aaa0b0e 100644 --- a/stdlib/source/lux/tool/mediator/parallelism.lux +++ b/stdlib/source/lux/tool/mediator/parallelism.lux @@ -2,13 +2,13 @@ [lux (#- Source Module) [control ["." monad (#+ Monad do)] + ["." try (#+ Try) ("#;." monad)] ["ex" exception (#+ exception:)]] [concurrency ["." promise (#+ Promise) ("#;." functor)] ["." task (#+ Task)] ["." stm (#+ Var STM)]] [data - ["." error (#+ Error) ("#;." monad)] ["." text ("#;." equivalence)] [collection ["." list ("#;." functor)] @@ -32,7 +32,7 @@ ["Dependency" dependency])) (type: Pending-Compilation - (Promise (Error (Ex [d] (Document d))))) + (Promise (Try (Ex [d] (Document d))))) (type: Active-Compilations (Dictionary Module [Descriptor Pending-Compilation])) @@ -72,9 +72,9 @@ (def: (share-compilation archive pending) (-> Active-Compilations Pending-Compilation (Task Archive)) - (promise;map (|>> (error;map (function (_ document) - (archive.add module document archive))) - error;join) + (promise;map (|>> (try;map (function (_ document) + (archive.add module document archive))) + try;join) pending)) (def: (import Monad<!> mediate archive dependencies) @@ -87,8 +87,8 @@ (All [d o] (-> Archive (List Archive) (Compilation d o) [Archive (Either (Compilation d o) [(Document d) (Output o)])])) - (do error.monad - [archive' (monad.fold error.monad archive.merge archive imports) + (do try.monad + [archive' (monad.fold try.monad archive.merge archive imports) outcome (process archive')] (case outcome (#.Right [document output]) @@ -128,7 +128,7 @@ #descriptor.file (get@ #compiler.file input) #descriptor.references (list) #descriptor.state #.Active} - pending (promise.promise (: (Maybe (Error (Ex [d] (Document d)))) + pending (promise.promise (: (Maybe (Try (Ex [d] (Document d)))) #.None))] updated (stm.update (dictionary.put (get@ #compiler.module input) [base-descriptor pending]) @@ -150,7 +150,7 @@ (recur archive' continue) (#.Right [document output]) - (exec (io.run (promise.resolve (#error.Success document) pending)) + (exec (io.run (promise.resolve (#try.Success document) pending)) (wrap archive')))))) (def: #export (mediator file-system sources compiler) |