From cd71a864ad5be13ed6ec6d046e0a2cb1087bdf94 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Fri, 10 Sep 2021 01:21:23 -0400 Subject: Migrated variants to the new syntax. --- .../source/program/aedifex/artifact/snapshot.lux | 12 +++--- .../program/aedifex/artifact/snapshot/build.lux | 2 +- .../program/aedifex/artifact/snapshot/stamp.lux | 4 +- .../program/aedifex/artifact/snapshot/version.lux | 4 +- .../aedifex/artifact/snapshot/version/value.lux | 2 +- .../source/program/aedifex/artifact/time/date.lux | 2 +- .../source/program/aedifex/artifact/versioning.lux | 6 +-- stdlib/source/program/aedifex/cli.lux | 8 ++-- stdlib/source/program/aedifex/command/auto.lux | 4 +- stdlib/source/program/aedifex/command/build.lux | 48 +++++++++++----------- stdlib/source/program/aedifex/command/deploy.lux | 2 +- stdlib/source/program/aedifex/command/deps.lux | 2 +- stdlib/source/program/aedifex/command/install.lux | 4 +- stdlib/source/program/aedifex/command/test.lux | 4 +- .../program/aedifex/dependency/deployment.lux | 20 ++++----- .../program/aedifex/dependency/resolution.lux | 42 +++++++++---------- .../source/program/aedifex/dependency/status.lux | 10 ++--- stdlib/source/program/aedifex/format.lux | 4 +- stdlib/source/program/aedifex/hash.lux | 4 +- stdlib/source/program/aedifex/input.lux | 8 ++-- .../source/program/aedifex/metadata/artifact.lux | 28 ++++++------- .../source/program/aedifex/metadata/snapshot.lux | 22 +++++----- stdlib/source/program/aedifex/package.lux | 12 +++--- stdlib/source/program/aedifex/parser.lux | 2 +- stdlib/source/program/aedifex/pom.lux | 48 +++++++++++----------- stdlib/source/program/aedifex/project.lux | 4 +- stdlib/source/program/aedifex/repository.lux | 16 ++++---- stdlib/source/program/aedifex/repository/local.lux | 2 +- .../source/program/aedifex/repository/origin.lux | 4 +- .../source/program/aedifex/repository/remote.lux | 8 ++-- 30 files changed, 169 insertions(+), 169 deletions(-) (limited to 'stdlib/source/program/aedifex') diff --git a/stdlib/source/program/aedifex/artifact/snapshot.lux b/stdlib/source/program/aedifex/artifact/snapshot.lux index 0a0d5cd94..64ff5d7b7 100644 --- a/stdlib/source/program/aedifex/artifact/snapshot.lux +++ b/stdlib/source/program/aedifex/artifact/snapshot.lux @@ -18,7 +18,7 @@ (type: .public Snapshot (Variant #Local - (#Remote Stamp))) + {#Remote Stamp})) (implementation: any_equivalence (Equivalence Any) @@ -45,9 +45,9 @@ (def: local_copy_format XML - (#xml.Node - xml.attributes - (list (#xml.Text ..local_copy_value)))) + {#xml.Node + xml.attributes + (list {#xml.Text ..local_copy_value})}) (def: local_copy_parser (Parser Any) @@ -57,12 +57,12 @@ (def: .public (format snapshot) (-> Snapshot XML) - (<| (#xml.Node .. xml.attributes) + (<| {#xml.Node .. xml.attributes} (case snapshot #Local (list ..local_copy_format) - (#Remote stamp) + {#Remote stamp} (/stamp.format stamp)))) (def: .public parser diff --git a/stdlib/source/program/aedifex/artifact/snapshot/build.lux b/stdlib/source/program/aedifex/artifact/snapshot/build.lux index a7e9e2fc8..4960f5862 100644 --- a/stdlib/source/program/aedifex/artifact/snapshot/build.lux +++ b/stdlib/source/program/aedifex/artifact/snapshot/build.lux @@ -33,7 +33,7 @@ (|>> %.nat #xml.Text list - (#xml.Node ..tag xml.attributes))) + {#xml.Node ..tag xml.attributes})) (def: .public parser (Parser Build) diff --git a/stdlib/source/program/aedifex/artifact/snapshot/stamp.lux b/stdlib/source/program/aedifex/artifact/snapshot/stamp.lux index 0a951c097..a840bd3c0 100644 --- a/stdlib/source/program/aedifex/artifact/snapshot/stamp.lux +++ b/stdlib/source/program/aedifex/artifact/snapshot/stamp.lux @@ -35,9 +35,9 @@ (def: time_format (-> Time XML) (|>> //time.format - #xml.Text + {#xml.Text} list - (#xml.Node .. xml.attributes))) + {#xml.Node .. xml.attributes})) (def: .public (format (^slots [#time #build])) (-> Stamp (List XML)) diff --git a/stdlib/source/program/aedifex/artifact/snapshot/version.lux b/stdlib/source/program/aedifex/artifact/snapshot/version.lux index 33238b990..2dac99df9 100644 --- a/stdlib/source/program/aedifex/artifact/snapshot/version.lux +++ b/stdlib/source/program/aedifex/artifact/snapshot/version.lux @@ -43,11 +43,11 @@ (def: (text_format tag value) (-> xml.Tag Text XML) - (|> value #xml.Text list (#xml.Node tag xml.attributes))) + (|> value #xml.Text list {#xml.Node tag xml.attributes})) (def: .public (format (^slots [#extension #value #updated])) (-> Version XML) - (<| (#xml.Node .. xml.attributes) + (<| {#xml.Node .. xml.attributes} (list (..text_format .. extension) (..text_format .. value) (..text_format .. (///time.format updated))))) diff --git a/stdlib/source/program/aedifex/artifact/snapshot/version/value.lux b/stdlib/source/program/aedifex/artifact/snapshot/version/value.lux index dc3744f4f..5f1816b3e 100644 --- a/stdlib/source/program/aedifex/artifact/snapshot/version/value.lux +++ b/stdlib/source/program/aedifex/artifact/snapshot/version/value.lux @@ -35,7 +35,7 @@ #///.Local version - (#///.Remote stamp) + {#///.Remote stamp} (let [(^slots [#///stamp.time #///stamp.build]) stamp] (%.format (text.replaced ..snapshot (///time.format time) diff --git a/stdlib/source/program/aedifex/artifact/time/date.lux b/stdlib/source/program/aedifex/artifact/time/date.lux index 3da3c1b86..167d0d2a2 100644 --- a/stdlib/source/program/aedifex/artifact/time/date.lux +++ b/stdlib/source/program/aedifex/artifact/time/date.lux @@ -51,7 +51,7 @@ (if (or (i.< ..min_year year) (i.> ..max_year year)) (exception.except ..year_is_out_of_range [(date.year raw)]) - (#try.Success (:abstraction raw))))) + {#try.Success (:abstraction raw)}))) (def: .public value (-> Date date.Date) diff --git a/stdlib/source/program/aedifex/artifact/versioning.lux b/stdlib/source/program/aedifex/artifact/versioning.lux index 644af3fa1..cf30987d2 100644 --- a/stdlib/source/program/aedifex/artifact/versioning.lux +++ b/stdlib/source/program/aedifex/artifact/versioning.lux @@ -59,16 +59,16 @@ (def: last_updated_format (-> //time.Time XML) - (|>> //time.format #xml.Text list (#xml.Node .. xml.attributes))) + (|>> //time.format #xml.Text list {#xml.Node .. xml.attributes})) (def: .public (format (^slots [#snapshot #last_updated #versions])) (-> Versioning XML) - (<| (#xml.Node .. xml.attributes) + (<| {#xml.Node .. xml.attributes} (list (//snapshot.format snapshot) (..last_updated_format last_updated) (|> versions (list\each //snapshot/version.format) - (#xml.Node .. xml.attributes))))) + {#xml.Node .. xml.attributes})))) (def: (text tag) (-> xml.Tag (Parser Text)) diff --git a/stdlib/source/program/aedifex/cli.lux b/stdlib/source/program/aedifex/cli.lux index 04706756f..fc4cf5440 100644 --- a/stdlib/source/program/aedifex/cli.lux +++ b/stdlib/source/program/aedifex/cli.lux @@ -44,9 +44,9 @@ #POM #Dependencies #Install - (#Deploy Text Identity) - (#Compilation Compilation) - (#Auto Compilation))) + {#Deploy Text Identity} + {#Compilation Compilation} + {#Auto Compilation})) (def: .public equivalence (Equivalence Command) @@ -97,7 +97,7 @@ (do <>.monad [head cli.any [tail command] command] - (in [(#.Item head tail) command]))) + (in [{#.Item head tail} command]))) (\ <>.monad each (|>> [(list /.default)]) ..command') )))) diff --git a/stdlib/source/program/aedifex/command/auto.lux b/stdlib/source/program/aedifex/command/auto.lux index dc065c399..0b82f4d81 100644 --- a/stdlib/source/program/aedifex/command/auto.lux +++ b/stdlib/source/program/aedifex/command/auto.lux @@ -41,7 +41,7 @@ (def: (pause delay) (-> Nat (Async (Try Any))) - (async.after delay (#try.Success []))) + (async.after delay {#try.Success []})) (def: .public (do! delay watcher command) (All (_ a) @@ -65,7 +65,7 @@ [_ (..pause delay) events (\ watcher poll [])] (case events - (#.Item _) + {#.Item _} (do ! [_ ] (recur [])) diff --git a/stdlib/source/program/aedifex/command/build.lux b/stdlib/source/program/aedifex/command/build.lux index 7d4592179..63d2affb7 100644 --- a/stdlib/source/program/aedifex/command/build.lux +++ b/stdlib/source/program/aedifex/command/build.lux @@ -51,7 +51,7 @@ (list.one (function (_ [dependency package]) (if (and (text\= group (value@ [#///dependency.artifact #///artifact.group] dependency)) (text\= name (value@ [#///dependency.artifact #///artifact.name] dependency))) - (#.Some dependency) + {#.Some dependency} #.None))))) (def: .public lux_group @@ -75,11 +75,11 @@ (type: .public Compiler (Variant - (#JVM Dependency) - (#JS Dependency) - (#Python Dependency) - (#Lua Dependency) - (#Ruby Dependency))) + {#JVM Dependency} + {#JS Dependency} + {#Python Dependency} + {#Lua Dependency} + {#Ruby Dependency})) (def: (remove_dependency dependency) (-> Dependency (-> Resolution Resolution)) @@ -91,12 +91,12 @@ (-> Resolution Dependency (Try [Resolution Compiler])) (let [[[compiler_group compiler_name compiler_version] compiler_type] compiler_dependency] (case (..dependency_finder compiler_group compiler_name resolution) - (#.Some dependency) + {#.Some dependency} (case compiler_name (^template [ ] [(^ (static )) - (#try.Success [(..remove_dependency dependency resolution) - ( dependency)])]) + {#try.Success [(..remove_dependency dependency resolution) + { dependency}]}]) ([#JVM ..jvm_compiler_name] [#JS ..js_compiler_name] [#Python ..python_compiler_name] @@ -139,16 +139,16 @@ (loop [left (text.all_split_by ..version_separator left) right (text.all_split_by ..version_separator right)] (case [left right] - [(#.Item leftH leftT) (#.Item rightH rightT)] + [{#.Item leftH leftT} {#.Item rightH rightT}] (if (text\= leftH rightH) (recur leftT rightT) (or (n.< (text.size leftH) (text.size rightH)) (text\< leftH rightH))) - [(#.Item leftH leftT) #.End] + [{#.Item leftH leftT} #.End] false - [#.End (#.Item rightH rightT)] + [#.End {#.Item rightH rightT}] true [#.End #.End] @@ -166,7 +166,7 @@ (value@ #///artifact.name artifact)] version (value@ #///artifact.version artifact)] (case (dictionary.value identity uniques) - (#.Some [current_version current_path]) + {#.Some [current_version current_path]} (if (\ version_order < version current_version) (dictionary.has identity [version dependency] uniques) uniques) @@ -203,18 +203,18 @@ _ (|> (\ process []) (async.upon! (function (recur ?line) (case ?line - (#try.Failure error) + {#try.Failure error} (if (exception.match? shell.no_more_output error) - (write! (#try.Success [])) + (write! {#try.Success []}) (async.upon! write! (console.write_line error console))) - (#try.Success line) + {#try.Success line} (async.upon! (function (_ outcome) (case outcome - (#try.Failure error) - (write! (#try.Failure error)) + {#try.Failure error} + (write! {#try.Failure error}) - (#try.Success _) + {#try.Success _} (async.upon! recur (\ process [])))) (console.write_line line console))))) @@ -245,7 +245,7 @@ (def: (jvm_class_path host_dependencies) (-> (List Path) Text) (|> host_dependencies - (#.Item ".") + {#.Item "."} (text.interposed ..jvm_class_path_separator))) (def: .public (with_jvm_class_path host_dependencies runtime) @@ -267,7 +267,7 @@ #.None (async\in (exception.except ..no_specified_program [])) - (#.Some program_module) + {#.Some program_module} (do async.monad [environment (program.environment async.monad program) .let [home (\ program home) @@ -276,14 +276,14 @@ [[resolution compiler] (async\in (..compiler resolution (value@ #///.compiler profile))) .let [host_dependencies (..host_dependencies fs home resolution) [[command compiler_params] output] (case compiler - (#JVM dependency) + {#JVM dependency} [(|> (value@ #///.java profile) (with@ #///runtime.parameters (list "program._")) - (with_jvm_class_path (#.Item (..path fs home dependency) host_dependencies))) + (with_jvm_class_path {#.Item (..path fs home dependency) host_dependencies})) "program.jar"] (^template [ ] - [( dependency) + [{ dependency} [(|> dependency (..path fs home) (///runtime.for (value@ profile))) diff --git a/stdlib/source/program/aedifex/command/deploy.lux b/stdlib/source/program/aedifex/command/deploy.lux index ee2cc3c71..4d18f1b18 100644 --- a/stdlib/source/program/aedifex/command/deploy.lux +++ b/stdlib/source/program/aedifex/command/deploy.lux @@ -71,7 +71,7 @@ (let [pom_data (|> pom (\ xml.codec encoded) (\ utf8.codec encoded))] - [#///package.origin (#///repository/origin.Remote "") + [#///package.origin {#///repository/origin.Remote ""} #///package.library [library (///dependency/status.verified library)] #///package.pom [pom diff --git a/stdlib/source/program/aedifex/command/deps.lux b/stdlib/source/program/aedifex/command/deps.lux index 0cce84d7c..f26a76211 100644 --- a/stdlib/source/program/aedifex/command/deps.lux +++ b/stdlib/source/program/aedifex/command/deps.lux @@ -42,7 +42,7 @@ (do async.monad [.let [dependencies (|> (value@ #///.dependencies profile) set.list - (#.Item (value@ #///.compiler profile)))] + {#.Item (value@ #///.compiler profile)})] [local_successes local_failures cache] (///dependency/resolution.all console (list local) new_repository diff --git a/stdlib/source/program/aedifex/command/install.lux b/stdlib/source/program/aedifex/command/install.lux index 660d82477..65575f63f 100644 --- a/stdlib/source/program/aedifex/command/install.lux +++ b/stdlib/source/program/aedifex/command/install.lux @@ -52,7 +52,7 @@ (def: .public (do! console fs repository profile) (-> (Console Async) (file.System Async) (Repository Async) (Command Any)) (case (value@ #/.identity profile) - (#.Some identity) + {#.Some identity} (do ///action.monad [package (|> profile (value@ #/.sources) @@ -66,7 +66,7 @@ (let [pom_data (|> pom (\ xml.codec encoded) (\ utf8.codec encoded))] - [#///package.origin (#///origin.Local "") + [#///package.origin {#///origin.Local ""} #///package.library (let [library (binary.result tar.writer package)] [library (///dependency/status.verified library)]) #///package.pom [pom diff --git a/stdlib/source/program/aedifex/command/test.lux b/stdlib/source/program/aedifex/command/test.lux index 35c805645..3e5cad3c6 100644 --- a/stdlib/source/program/aedifex/command/test.lux +++ b/stdlib/source/program/aedifex/command/test.lux @@ -42,13 +42,13 @@ [_ (console.write_line ..start console) .let [host_dependencies (//build.host_dependencies fs home resolution) [test_command test_parameters] (case compiler - (#//build.JVM dependency) + {#//build.JVM dependency} (|> program (///runtime.for (value@ #///.java profile)) (//build.with_jvm_class_path host_dependencies)) (^template [ ] - [( artifact) + [{ artifact} (///runtime.for (value@ profile) program)]) ([#//build.JS #///.js] diff --git a/stdlib/source/program/aedifex/dependency/deployment.lux b/stdlib/source/program/aedifex/dependency/deployment.lux index fa6da0bc0..84170965c 100644 --- a/stdlib/source/program/aedifex/dependency/deployment.lux +++ b/stdlib/source/program/aedifex/dependency/deployment.lux @@ -56,15 +56,15 @@ #///dependency/status.Unverified (in []) - (#///dependency/status.Partial partial) + {#///dependency/status.Partial partial} (case partial - (#.Left sha-1) + {#.Left sha-1} (deploy_hash ///hash.sha-1_codec ///artifact/extension.sha-1 sha-1) - (#.Right md5) + {#.Right md5} (deploy_hash ///hash.md5_codec ///artifact/extension.md5 md5)) - (#///dependency/status.Verified sha-1 md5) + {#///dependency/status.Verified sha-1 md5} (do ! [_ (deploy_hash ///hash.sha-1_codec ///artifact/extension.sha-1 sha-1)] (deploy_hash ///hash.md5_codec ///artifact/extension.md5 md5)))))) @@ -78,12 +78,12 @@ #///dependency/status.Unverified (list) - (#///dependency/status.Partial partial) + {#///dependency/status.Partial partial} (list (case partial - (#.Left _) - (#.Right _) )) + {#.Left _} + {#.Right _} )) - (#///dependency/status.Verified _) + {#///dependency/status.Verified _} (list ))))) (def: (update_snapshot [artifact type] now snapshot) @@ -99,8 +99,8 @@ #///artifact/snapshot.Local #///artifact/snapshot.Local - (#///artifact/snapshot.Remote [_ build]) - (#///artifact/snapshot.Remote [now (++ build)])))) + {#///artifact/snapshot.Remote [_ build]} + {#///artifact/snapshot.Remote [now (++ build)]}))) (with@ [#///metadata/snapshot.versioning #///artifact/versioning.last_updated] now)) versioning_snapshot (value@ [#///metadata/snapshot.versioning #///artifact/versioning.snapshot] snapshot)]] (in (|> snapshot diff --git a/stdlib/source/program/aedifex/dependency/resolution.lux b/stdlib/source/program/aedifex/dependency/resolution.lux index ce54d9d9a..3c8241595 100644 --- a/stdlib/source/program/aedifex/dependency/resolution.lux +++ b/stdlib/source/program/aedifex/dependency/resolution.lux @@ -85,7 +85,7 @@ (do async.monad [?actual (\ repository download (///repository/remote.uri version_template artifact extension))] (case ?actual - (#try.Success actual) + {#try.Success actual} (in (do [! try.monad] [output (\ ! each (for [@.old (|>> (:as java/lang/String) java/lang/String::trim @@ -99,10 +99,10 @@ (\ codec decoded)) _ (exception.assertion exception [artifact extension output] (\ ///hash.equivalence = (hash library) actual))] - (in (#.Some actual)))) + (in {#.Some actual}))) - (#try.Failure error) - (in (#try.Success #.None))))) + {#try.Failure error} + (in {#try.Success #.None})))) (def: (hashed repository version_template artifact extension) (-> (Repository Async) Version Artifact Extension (Async (Try [Binary Status]))) @@ -115,14 +115,14 @@ repository version_template artifact (format extension ///artifact/extension.md5) ///hash.md5 ///hash.md5_codec ..md5_does_not_match)] (in [data (case [?sha-1 ?md5] - [(#.Some sha-1) (#.Some md5)] - (#//status.Verified sha-1 md5) + [{#.Some sha-1} {#.Some md5}] + {#//status.Verified sha-1 md5} - [(#.Some sha-1) #.None] - (#//status.Partial (#.Left sha-1)) + [{#.Some sha-1} #.None] + {#//status.Partial {#.Left sha-1}} - [#.None (#.Some md5)] - (#//status.Partial (#.Right md5)) + [#.None {#.Some md5}] + {#//status.Partial {#.Right md5}} [#.None #.None] #//status.Unverified)]))) @@ -144,7 +144,7 @@ [pom (\ utf8.codec decoded pom_data) pom (\ xml.codec decoded pom) profile (.result ///pom.parser (list pom))] - (in [#///package.origin (#///repository/origin.Remote "") + (in [#///package.origin {#///repository/origin.Remote ""} #///package.library library_&_status #///package.pom [pom pom_data pom_status]])))))) @@ -187,17 +187,17 @@ (exception.except ..cannot_resolve) (\ async.monad in)) - (#.Item repository alternatives) + {#.Item repository alternatives} (do [! async.monad] [_ (..announce_fetching console repository (value@ #//.artifact dependency)) outcome (..one repository dependency)] (case outcome - (#try.Success package) + {#try.Success package} (do ! [_ (..announce_success console repository (value@ #//.artifact dependency))] (in outcome)) - (#try.Failure error) + {#try.Failure error} (do ! [_ (..announce_failure console repository (value@ #//.artifact dependency))] (any console alternatives dependency)))))) @@ -217,7 +217,7 @@ (\ async.monad in [successes failures resolution]) - (#.Item head tail) + {#.Item head tail} (case (value@ [#//.artifact #///artifact.version] head) ... Skip if there is no version "" (recur repositories @@ -227,13 +227,13 @@ resolution) _ (do [! async.monad] [?package (case (dictionary.value head resolution) - (#.Some package) - (in (#try.Success package)) + {#.Some package} + (in {#try.Success package}) #.None (..any console repositories head))] (case ?package - (#try.Success package) + {#try.Success package} (do ! [.let [redundant? (: (Predicate Dependency) (predicate.or (\ //.equivalence = head) @@ -252,15 +252,15 @@ ... sub_repositories (list\composite repositories package_repositories) ]] (recur repositories - (#.Item head successes) + {#.Item head successes} failures (set.list (set.union (set.of_list //.hash tail) (set.of_list //.hash sub_dependencies))) (dictionary.has head package resolution))) - (#try.Failure error) + {#try.Failure error} (recur repositories successes - (#.Item head failures) + {#.Item head failures} tail resolution))))))) diff --git a/stdlib/source/program/aedifex/dependency/status.lux b/stdlib/source/program/aedifex/dependency/status.lux index f5439114e..150d3120b 100644 --- a/stdlib/source/program/aedifex/dependency/status.lux +++ b/stdlib/source/program/aedifex/dependency/status.lux @@ -13,9 +13,9 @@ (type: .public Status (Variant #Unverified - (#Partial (Either (Hash SHA-1) - (Hash MD5))) - (#Verified (Hash SHA-1) (Hash MD5)))) + {#Partial (Either (Hash SHA-1) + (Hash MD5))} + {#Verified (Hash SHA-1) (Hash MD5)})) (implementation: any_equivalence (Equivalence Any) @@ -37,6 +37,6 @@ (def: .public (verified payload) (-> Binary Status) - (#Verified + {#Verified (///hash.sha-1 payload) - (///hash.md5 payload))) + (///hash.md5 payload)}) diff --git a/stdlib/source/program/aedifex/format.lux b/stdlib/source/program/aedifex/format.lux index 3f626f0e2..5f7669366 100644 --- a/stdlib/source/program/aedifex/format.lux +++ b/stdlib/source/program/aedifex/format.lux @@ -44,7 +44,7 @@ (`' [#name (~ (code.text name)) #url (~ (code.text url))]) - (#.Some value) + {#.Some value} (`' [#name (~ (code.text name)) #url (~ (code.text url)) #organization (~ (..organization value))]))) @@ -75,7 +75,7 @@ #.None aggregate - (#.Some value) + {#.Some value} (dictionary.has field (format value) aggregate))) (def: (on_list field value format aggregate) diff --git a/stdlib/source/program/aedifex/hash.lux b/stdlib/source/program/aedifex/hash.lux index 74e54679f..b25dedbb3 100644 --- a/stdlib/source/program/aedifex/hash.lux +++ b/stdlib/source/program/aedifex/hash.lux @@ -99,7 +99,7 @@ [(def: .public ( data) (-> Binary (Try (Hash ))) (if (n.= (binary.size data)) - (#try.Success (:abstraction data)) + {#try.Success (:abstraction data)} (exception.except [data])))] [as_sha-1 SHA-1 ..sha-1::size ..not_a_sha-1] @@ -125,7 +125,7 @@ output (binary.empty hash_size)] (let [index (n.* chunk i64.bytes_per_i64)] (case (text.split_at ..hex_per_chunk input) - (#.Some [head tail]) + {#.Some [head tail]} (do try.monad [head (\ n.hex decoded head) output (binary.write/64! index head output)] diff --git a/stdlib/source/program/aedifex/input.lux b/stdlib/source/program/aedifex/input.lux index 02e212744..aa76979a8 100644 --- a/stdlib/source/program/aedifex/input.lux +++ b/stdlib/source/program/aedifex/input.lux @@ -36,11 +36,11 @@ syntax.no_aliases (text.size source_code))] (case (parse [location.dummy 0 source_code]) - (#.Left [_ error]) - (#try.Failure error) + {#.Left [_ error]} + {#try.Failure error} - (#.Right [_ lux_code]) - (#try.Success lux_code)))) + {#.Right [_ lux_code]} + {#try.Success lux_code}))) (def: project_parser (-> Binary (Try Project)) diff --git a/stdlib/source/program/aedifex/metadata/artifact.lux b/stdlib/source/program/aedifex/metadata/artifact.lux index 571d9bff1..b56c66104 100644 --- a/stdlib/source/program/aedifex/metadata/artifact.lux +++ b/stdlib/source/program/aedifex/metadata/artifact.lux @@ -84,7 +84,7 @@ (template [
]
   [(def: 
      (->  XML)
-     (|>> 
 #xml.Text list (#xml.Node  xml.attributes)))]
+     (|>> 
 {#xml.Text} list {#xml.Node  xml.attributes}))]
 
   [group_format Group .. (|>)]
   [name_format Name .. (|>)]
@@ -94,18 +94,18 @@
 
 (def: versions_format
   (-> (List Version) XML)
-  (|>> (list\each ..version_format) (#xml.Node .. xml.attributes)))
+  (|>> (list\each ..version_format) {#xml.Node .. xml.attributes}))
 
 (def: .public (format value)
   (-> Metadata XML)
-  (#xml.Node ..
-             xml.attributes
-             (list (..group_format (value@ #group value))
-                   (..name_format (value@ #name value))
-                   (#xml.Node ..
-                              xml.attributes
-                              (list (..versions_format (value@ #versions value))
-                                    (..last_updated_format (value@ #last_updated value)))))))
+  {#xml.Node ..
+   xml.attributes
+   (list (..group_format (value@ #group value))
+         (..name_format (value@ #name value))
+         {#xml.Node ..
+          xml.attributes
+          (list (..versions_format (value@ #versions value))
+                (..last_updated_format (value@ #last_updated value)))})})
 
 (def: (text tag)
   (-> xml.Tag (Parser Text))
@@ -178,20 +178,20 @@
   (do async.monad
     [project (\ repository download (..uri artifact))]
     (case project
-      (#try.Success project)
+      {#try.Success project}
       (in (|> project
               (do> try.monad
                    [(\ utf8.codec decoded)]
                    [(\ xml.codec decoded)]
                    [list (.result ..parser)])))
       
-      (#try.Failure error)
-      (in (#try.Success
+      {#try.Failure error}
+      (in {#try.Success
            (let [(^slots [#///artifact.group #///artifact.name]) artifact]
              [#group group
               #name name
               #versions (list)
-              #last_updated ..epoch]))))))
+              #last_updated ..epoch])}))))
 
 (def: .public (write repository artifact metadata)
   (-> (Repository Async) Artifact Metadata (Async (Try Any)))
diff --git a/stdlib/source/program/aedifex/metadata/snapshot.lux b/stdlib/source/program/aedifex/metadata/snapshot.lux
index 53f5faee0..58792b042 100644
--- a/stdlib/source/program/aedifex/metadata/snapshot.lux
+++ b/stdlib/source/program/aedifex/metadata/snapshot.lux
@@ -62,7 +62,7 @@
 (template [   
]
   [(def: 
      (->  XML)
-     (|>> 
 #xml.Text list (#xml.Node  xml.attributes)))]
+     (|>> 
 #xml.Text list {#xml.Node  xml.attributes}))]
 
   [group_format Group .. (|>)]
   [name_format Name .. (|>)]
@@ -72,12 +72,12 @@
 (def: .public (format (^slots [#artifact #versioning]))
   (-> Metadata XML)
   (let [(^slots [#///artifact.group #///artifact.name #///artifact.version]) artifact]
-    (#xml.Node ..
-               xml.attributes
-               (list (..group_format group)
-                     (..name_format name)
-                     (..version_format version)
-                     (///artifact/versioning.format versioning)))))
+    {#xml.Node ..
+     xml.attributes
+     (list (..group_format group)
+           (..name_format name)
+           (..version_format version)
+           (///artifact/versioning.format versioning))}))
 
 (def: (text tag)
   (-> xml.Tag (Parser Text))
@@ -128,17 +128,17 @@
   (do async.monad
     [project (\ repository download (..uri artifact))]
     (case project
-      (#try.Success project)
+      {#try.Success project}
       (in (|> project
               (do> try.monad
                    [(\ utf8.codec decoded)]
                    [(\ xml.codec decoded)]
                    [list (.result ..parser)])))
       
-      (#try.Failure error)
-      (in (#try.Success
+      {#try.Failure error}
+      (in {#try.Success
            [#artifact artifact
-            #versioning ///artifact/versioning.init])))))
+            #versioning ///artifact/versioning.init]}))))
 
 (def: .public (write repository artifact metadata)
   (-> (Repository Async) Artifact Metadata (Async (Try Any)))
diff --git a/stdlib/source/program/aedifex/package.lux b/stdlib/source/program/aedifex/package.lux
index bd149b0d9..62757c9b0 100644
--- a/stdlib/source/program/aedifex/package.lux
+++ b/stdlib/source/program/aedifex/package.lux
@@ -38,7 +38,7 @@
   [(def: .public ( package)
      (-> Package Bit)
      (case (value@ #origin package)
-       ( _)
+       { _}
        true
        
        _
@@ -50,15 +50,15 @@
 
 (def: .public (local pom library)
   (-> XML Binary Package)
-  [#origin (#//origin.Local "")
+  [#origin {#//origin.Local ""}
    #library [library
-             (#//status.Verified (//hash.sha-1 library)
-                                 (//hash.md5 library))]
+             {#//status.Verified (//hash.sha-1 library)
+              (//hash.md5 library)}]
    #pom (let [binary_pom (|> pom (\ xml.codec encoded) (\ utf8.codec encoded))]
           [pom
            binary_pom
-           (#//status.Verified (//hash.sha-1 binary_pom)
-                               (//hash.md5 binary_pom))])])
+           {#//status.Verified (//hash.sha-1 binary_pom)
+            (//hash.md5 binary_pom)}])])
 
 (def: .public dependencies
   (-> Package (Try (Set Dependency)))
diff --git a/stdlib/source/program/aedifex/parser.lux b/stdlib/source/program/aedifex/parser.lux
index 02840c2ec..b3239d4e2 100644
--- a/stdlib/source/program/aedifex/parser.lux
+++ b/stdlib/source/program/aedifex/parser.lux
@@ -31,7 +31,7 @@
 (def: (as_input input)
   (-> (Maybe Code) (List Code))
   (case input
-    (#.Some input)
+    {#.Some input}
     (list input)
     
     #.None
diff --git a/stdlib/source/program/aedifex/pom.lux b/stdlib/source/program/aedifex/pom.lux
index 7cf6f961e..49e3793fe 100644
--- a/stdlib/source/program/aedifex/pom.lux
+++ b/stdlib/source/program/aedifex/pom.lux
@@ -47,14 +47,14 @@
 
 (def: version
   XML
-  (#_.Node ["" "modelVersion"] _.attributes
-           (list (#_.Text "4.0.0"))))
+  {#_.Node ["" "modelVersion"] _.attributes
+   (list {#_.Text "4.0.0"})})
 
 (def: (property tag value)
   (-> Text Text XML)
-  (#_.Node ["" tag]
-           _.attributes
-           (list (#_.Text value))))
+  {#_.Node ["" tag]
+   _.attributes
+   (list {#_.Text value})})
 
 (def: (artifact value)
   (-> Artifact (List XML))
@@ -73,37 +73,37 @@
   (|> (list (..property "name" name)
             (..property ..url_tag url)
             (..distribution distribution))
-      (#_.Node ["" "license"] _.attributes)))
+      {#_.Node ["" "license"] _.attributes}))
 
 (def: repository
   (-> Address XML)
   (|>> (..property ..url_tag)
        list
-       (#_.Node ["" ..repository_tag] _.attributes)))
+       {#_.Node ["" ..repository_tag] _.attributes}))
 
 (def: (dependency value)
   (-> Dependency XML)
-  (#_.Node ["" ..dependency_tag]
-           _.attributes
-           (list\composite (..artifact (value@ #//dependency.artifact value))
-                           (list (..property "type" (value@ #//dependency.type value))))))
+  {#_.Node ["" ..dependency_tag]
+   _.attributes
+   (list\composite (..artifact (value@ #//dependency.artifact value))
+                   (list (..property "type" (value@ #//dependency.type value))))})
 
 (def: (group tag)
   (-> Text (-> (List XML) XML))
-  (|>> (#_.Node ["" tag] _.attributes)))
+  (|>> {#_.Node ["" tag] _.attributes}))
 
 (comment
   (def: scm
     (-> /.SCM XML)
     (|>> (..property ..url_tag)
          list
-         (#_.Node ["" "scm"] _.attributes)))
+         {#_.Node ["" "scm"] _.attributes}))
 
   (def: (organization [name url])
     (-> /.Organization XML)
     (|> (list (..property "name" name)
               (..property ..url_tag url))
-        (#_.Node ["" "organization"] _.attributes)))
+        {#_.Node ["" "organization"] _.attributes}))
 
   (def: (developer_organization [name url])
     (-> /.Organization (List XML))
@@ -119,7 +119,7 @@
   (template [  ]
     [(def: 
        (->  XML)
-       (|>> ..developer' (#_.Node ["" ] _.attributes)))]
+       (|>> ..developer' {#_.Node ["" ] _.attributes}))]
 
     [developer /.Developer "developer"]
     [contributor /.Contributor "contributor"]
@@ -141,15 +141,15 @@
 (def: .public (write value)
   (-> /.Profile (Try XML))
   (case (value@ #/.identity value)
-    (#.Some identity)
-    (#try.Success
-     (#_.Node ["" ..project_tag] _.attributes
-              ($_ list\composite
-                  (list ..version)
-                  (..artifact identity)
-                  (|> value (value@ #/.repositories) set.list (list\each ..repository) (..group "repositories") list)
-                  (|> value (value@ #/.dependencies) set.list (list\each ..dependency) (..group ..dependencies_tag) list)
-                  )))
+    {#.Some identity}
+    {#try.Success
+     {#_.Node ["" ..project_tag] _.attributes
+      ($_ list\composite
+          (list ..version)
+          (..artifact identity)
+          (|> value (value@ #/.repositories) set.list (list\each ..repository) (..group "repositories") list)
+          (|> value (value@ #/.dependencies) set.list (list\each ..dependency) (..group ..dependencies_tag) list)
+          )}}
 
     _
     (exception.except /.no_identity [])))
diff --git a/stdlib/source/program/aedifex/project.lux b/stdlib/source/program/aedifex/project.lux
index 1d1d55998..acf3c3819 100644
--- a/stdlib/source/program/aedifex/project.lux
+++ b/stdlib/source/program/aedifex/project.lux
@@ -54,10 +54,10 @@
 (def: (profile' lineage project name)
   (-> (Set Name) Project Name (Try Profile))
   (case (dictionary.value name project)
-    (#.Some profile)
+    {#.Some profile}
     (case (list.example (set.member? lineage)
                         (value@ #//.parents profile))
-      (#.Some ouroboros)
+      {#.Some ouroboros}
       (exception.except ..circular_dependency [ouroboros name])
       
       #.None
diff --git a/stdlib/source/program/aedifex/repository.lux b/stdlib/source/program/aedifex/repository.lux
index 5cca8174b..b836cfa54 100644
--- a/stdlib/source/program/aedifex/repository.lux
+++ b/stdlib/source/program/aedifex/repository.lux
@@ -57,24 +57,24 @@
         (do [! stm.monad]
           [|state| (stm.read state)]
           (case (\ mock on_download uri |state|)
-            (#try.Success [|state| output])
+            {#try.Success [|state| output]}
             (do !
               [_ (stm.write |state| state)]
-              (in (#try.Success output)))
+              (in {#try.Success output}))
             
-            (#try.Failure error)
-            (in (#try.Failure error))))))
+            {#try.Failure error}
+            (in {#try.Failure error})))))
 
      (def: (upload uri content)
        (stm.commit!
         (do [! stm.monad]
           [|state| (stm.read state)]
           (case (\ mock on_upload uri content |state|)
-            (#try.Success |state|)
+            {#try.Success |state|}
             (do !
               [_ (stm.write |state| state)]
-              (in (#try.Success [])))
+              (in {#try.Success []}))
             
-            (#try.Failure error)
-            (in (#try.Failure error))))))
+            {#try.Failure error}
+            (in {#try.Failure error})))))
      )))
diff --git a/stdlib/source/program/aedifex/repository/local.lux b/stdlib/source/program/aedifex/repository/local.lux
index 2c528a520..508fcba28 100644
--- a/stdlib/source/program/aedifex/repository/local.lux
+++ b/stdlib/source/program/aedifex/repository/local.lux
@@ -53,7 +53,7 @@
        _ (if ?
            (in [])
            (case (file.parent fs absolute_path)
-             (#.Some parent)
+             {#.Some parent}
              (file.make_directories async.monad fs parent)
 
              _
diff --git a/stdlib/source/program/aedifex/repository/origin.lux b/stdlib/source/program/aedifex/repository/origin.lux
index 72163f641..a5a613a1a 100644
--- a/stdlib/source/program/aedifex/repository/origin.lux
+++ b/stdlib/source/program/aedifex/repository/origin.lux
@@ -12,8 +12,8 @@
 
 (type: .public Origin
   (Variant
-   (#Local Path)
-   (#Remote URL)))
+   {#Local Path}
+   {#Remote URL}))
 
 (def: .public equivalence
   (Equivalence Origin)
diff --git a/stdlib/source/program/aedifex/repository/remote.lux b/stdlib/source/program/aedifex/repository/remote.lux
index 4f852c2b7..269ff15a9 100644
--- a/stdlib/source/program/aedifex/repository/remote.lux
+++ b/stdlib/source/program/aedifex/repository/remote.lux
@@ -73,7 +73,7 @@
         
         _
         (do !
-          [_ ((value@ #@http.body message) (#.Some 0))]
+          [_ ((value@ #@http.body message) {#.Some 0})]
           (\ io.monad in (exception.except ..download_failure [(format address uri) status]))))))
 
   (def: (upload uri content)
@@ -84,12 +84,12 @@
                                                      #.None
                                                      ..base_headers
                                                      
-                                                     (#.Some [user password])
+                                                     {#.Some [user password]}
                                                      (list& ["Authorization" (//identity.basic_auth user password)]
                                                             ..base_headers)))
-                                     (#.Some content)
+                                     {#.Some content}
                                      http))
-       _ ((value@ #@http.body message) (#.Some 0))]
+       _ ((value@ #@http.body message) {#.Some 0})]
       (case status
         (^ (static http/status.created))
         (in [])
-- 
cgit v1.2.3