diff options
Diffstat (limited to 'stdlib/source/program')
-rw-r--r-- | stdlib/source/program/aedifex/command/auto.lux | 4 | ||||
-rw-r--r-- | stdlib/source/program/aedifex/command/build.lux | 12 | ||||
-rw-r--r-- | stdlib/source/program/aedifex/command/deps.lux | 2 | ||||
-rw-r--r-- | stdlib/source/program/aedifex/dependency/resolution.lux | 12 | ||||
-rw-r--r-- | stdlib/source/program/aedifex/format.lux | 2 | ||||
-rw-r--r-- | stdlib/source/program/compositor.lux | 4 | ||||
-rw-r--r-- | stdlib/source/program/scriptum.lux | 22 |
7 files changed, 29 insertions, 29 deletions
diff --git a/stdlib/source/program/aedifex/command/auto.lux b/stdlib/source/program/aedifex/command/auto.lux index a80193663..994f192fe 100644 --- a/stdlib/source/program/aedifex/command/auto.lux +++ b/stdlib/source/program/aedifex/command/auto.lux @@ -65,10 +65,10 @@ [_ (..pause delay) events (\ watcher poll [])] (case events - (#.Cons _) + (#.Item _) (do ! [_ <call>] (recur [])) - #.Nil + #.End (recur [])))))))))) diff --git a/stdlib/source/program/aedifex/command/build.lux b/stdlib/source/program/aedifex/command/build.lux index 6a0b6bcd0..b675bb5cd 100644 --- a/stdlib/source/program/aedifex/command/build.lux +++ b/stdlib/source/program/aedifex/command/build.lux @@ -139,19 +139,19 @@ (loop [left (text.split_all_with ..version_separator left) right (text.split_all_with ..version_separator right)] (case [left right] - [(#.Cons leftH leftT) (#.Cons 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))) - [(#.Cons leftH leftT) #.Nil] + [(#.Item leftH leftT) #.End] false - [#.Nil (#.Cons rightH rightT)] + [#.End (#.Item rightH rightT)] true - [#.Nil #.Nil] + [#.End #.End] false)))) (def: #export (host_dependencies fs home) @@ -245,14 +245,14 @@ (def: (jvm_class_path host_dependencies) (-> (List Path) Text) (|> host_dependencies - (#.Cons ".") + (#.Item ".") (text.join_with ..jvm_class_path_separator) %.text)) (def: #export (with_jvm_class_path host_dependencies runtime) (-> (List Path) ///runtime.Runtime ///runtime.Runtime) (case host_dependencies - #.Nil + #.End runtime _ diff --git a/stdlib/source/program/aedifex/command/deps.lux b/stdlib/source/program/aedifex/command/deps.lux index 434bedbdd..0238f64cd 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 (|> (get@ #///.dependencies profile) set.to_list - (#.Cons (get@ #///.compiler profile)))] + (#.Item (get@ #///.compiler profile)))] [local_successes local_failures cache] (///dependency/resolution.all console (list local) new_repository diff --git a/stdlib/source/program/aedifex/dependency/resolution.lux b/stdlib/source/program/aedifex/dependency/resolution.lux index 8c7b6ab6a..3bd510675 100644 --- a/stdlib/source/program/aedifex/dependency/resolution.lux +++ b/stdlib/source/program/aedifex/dependency/resolution.lux @@ -177,12 +177,12 @@ (def: #export (any console repositories dependency) (-> (Console Async) (List (Repository Async)) Dependency (Async (Try Package))) (case repositories - #.Nil + #.End (|> dependency (exception.except ..cannot_resolve) (\ async.monad in)) - (#.Cons repository alternatives) + (#.Item repository alternatives) (do {! async.monad} [_ (..announce_fetching console repository (get@ #//.artifact dependency)) outcome (..one repository dependency)] @@ -208,11 +208,11 @@ dependencies dependencies resolution resolution] (case dependencies - #.Nil + #.End (\ async.monad in [successes failures resolution]) - (#.Cons head tail) + (#.Item head tail) (case (get@ [#//.artifact #///artifact.version] head) ## Skip if there is no version "" (recur repositories @@ -243,7 +243,7 @@ ## sub_repositories (list\compose repositories package_repositories) sub_repositories repositories] [successes failures resolution] (recur sub_repositories - (#.Cons head successes) + (#.Item head successes) failures sub_dependencies (dictionary.put head package resolution))] @@ -256,6 +256,6 @@ (#try.Failure error) (recur repositories successes - (#.Cons head failures) + (#.Item head failures) tail resolution))))))) diff --git a/stdlib/source/program/aedifex/format.lux b/stdlib/source/program/aedifex/format.lux index 1896415ea..f87fcfaae 100644 --- a/stdlib/source/program/aedifex/format.lux +++ b/stdlib/source/program/aedifex/format.lux @@ -81,7 +81,7 @@ (All [a] (-> Text (List a) (Format a) Aggregate Aggregate)) (case value - #.Nil + #.End aggregate value diff --git a/stdlib/source/program/compositor.lux b/stdlib/source/program/compositor.lux index c804d86b0..5976c681a 100644 --- a/stdlib/source/program/compositor.lux +++ b/stdlib/source/program/compositor.lux @@ -101,10 +101,10 @@ output (: (Dictionary file.Path Binary) (dictionary.new text.hash))] (case pending - #.Nil + #.End (in output) - (#.Cons head tail) + (#.Item head tail) (do ! [content (\ fs read head)] (recur tail diff --git a/stdlib/source/program/scriptum.lux b/stdlib/source/program/scriptum.lux index 889ba4a0f..e429ff86f 100644 --- a/stdlib/source/program/scriptum.lux +++ b/stdlib/source/program/scriptum.lux @@ -109,7 +109,7 @@ (case [recursive_type? type] [_ (#.Primitive name params)] (case params - #.Nil + #.End (format "(primitive " (%.text name) ")") _ @@ -118,7 +118,7 @@ [_ (#.Sum _)] (let [members (type.flat_variant type)] (case tags - #.Nil + #.End (format "(| " (|> members (list\map (pprint_type_definition level type_func_info #.None module signature? recursive_type?)) @@ -145,7 +145,7 @@ [_ (#.Product _)] (let [members (type.flat_tuple type)] (case tags - #.Nil + #.End (format "[" (|> members (list\map (pprint_type_definition level type_func_info #.None module signature? recursive_type?)) (text.join_with " ")) "]") _ @@ -183,7 +183,7 @@ body_doc (pprint_type_definition (n.+ level level') type_func_info tags module signature? recursive_type? body)] (format "(" <name> " " "[" (text.join_with " " args) "]" (case tags - #.Nil + #.End (format " " body_doc) _ @@ -210,7 +210,7 @@ (case type (#.Primitive name params) (case params - #.Nil + #.End (format "(primitive " (%.text name) ")") _ @@ -285,25 +285,25 @@ (cond (type\= .Type def_type) (update@ #types (: (Mutation (List Value)) - (|>> (#.Cons [name def_annotations (:as Type def_value)]))) + (|>> (#.Item [name def_annotations (:as Type def_value)]))) organization) (type\= .Macro def_type) (update@ #macros (: (Mutation (List [Text Code])) - (|>> (#.Cons [name def_annotations]))) + (|>> (#.Item [name def_annotations]))) organization) (annotation.implementation? def_annotations) (update@ #implementations (: (Mutation (List Value)) - (|>> (#.Cons [name def_annotations def_type]))) + (|>> (#.Item [name def_annotations def_type]))) organization) ## else (update@ #values (: (Mutation (List Value)) - (|>> (#.Cons [name def_annotations def_type]))) + (|>> (#.Item [name def_annotations def_type]))) organization))) (def: name_sort @@ -359,7 +359,7 @@ type_arguments (annotation.type_arguments def_annotations) signature? (annotation.signature? def_annotations) usage (case type_arguments - #.Nil + #.End _name _ @@ -429,7 +429,7 @@ (list\map (function (_ [name def_annotations value_type]) (let [?doc (annotation.documentation def_annotations) usage (case (annotation.function_arguments def_annotations) - #.Nil + #.End name args |