aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/type/implicit.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/type/implicit.lux')
-rw-r--r--stdlib/source/library/lux/type/implicit.lux80
1 files changed, 40 insertions, 40 deletions
diff --git a/stdlib/source/library/lux/type/implicit.lux b/stdlib/source/library/lux/type/implicit.lux
index 03379a14e..1d32fd57c 100644
--- a/stdlib/source/library/lux/type/implicit.lux
+++ b/stdlib/source/library/lux/type/implicit.lux
@@ -29,19 +29,19 @@
(def: (type_var id env)
(-> Nat Type_Context (Meta Type))
(case (list.example (|>> product.left (n.= id))
- (value@ #.var_bindings env))
- {#.Some [_ {#.Some type}]}
+ (value@ .#var_bindings env))
+ {.#Some [_ {.#Some type}]}
(case type
- {#.Var id'}
+ {.#Var id'}
(type_var id' env)
_
(\ meta.monad in type))
- {#.Some [_ #.None]}
+ {.#Some [_ {.#None}]}
(meta.failure (format "Unbound type-var " (%.nat id)))
- #.None
+ {.#None}
(meta.failure (format "Unknown type-var " (%.nat id)))
))
@@ -51,8 +51,8 @@
[raw_type (meta.type var_name)
compiler meta.compiler_state]
(case raw_type
- {#.Var id}
- (type_var id (value@ #.type_context compiler))
+ {.#Var id}
+ (type_var id (value@ .#type_context compiler))
_
(in raw_type))))
@@ -60,18 +60,18 @@
(def: (member_type idx sig_type)
(-> Nat Type (Check Type))
(case sig_type
- {#.Named _ sig_type'}
+ {.#Named _ sig_type'}
(member_type idx sig_type')
- {#.Apply arg func}
+ {.#Apply arg func}
(case (type.applied (list arg) func)
- #.None
+ {.#None}
(check.failure (format "Cannot apply type " (%.type func) " to type " (%.type arg)))
- {#.Some sig_type'}
+ {.#Some sig_type'}
(member_type idx sig_type'))
- {#.Product left right}
+ {.#Product left right}
(if (n.= 0 idx)
(\ check.monad in left)
(member_type (-- idx) right))
@@ -97,10 +97,10 @@
candidates (list.only (|>> product.right (text\= simple_name))
tag_lists)]]
(case candidates
- #.End
+ {.#End}
(meta.failure (format "Unknown tag: " (%.name member)))
- {#.Item winner #.End}
+ {.#Item winner {.#End}}
(in winner)
_
@@ -139,7 +139,7 @@
(if (and (or (text\= target_module source_module)
exported?)
(compatible_type? sig_type def_type))
- {#.Item [[source_module name] def_type] aggregate}
+ {.#Item [[source_module name] def_type] aggregate}
aggregate))
aggregate
constants))
@@ -157,15 +157,15 @@
dictionary.entries
(list.all (function (_ [name type])
(if (compatible_type? sig_type type)
- {#.Some [["" name] type]}
- #.None)))))))
+ {.#Some [["" name] type]}
+ {.#None})))))))
(def: (local_structs sig_type)
(-> Type (Meta (List [Name Type])))
(do [! meta.monad]
[this_module_name meta.current_module_name
definitions (meta.definitions this_module_name)]
- (in (available_definitions sig_type this_module_name this_module_name definitions #.End))))
+ (in (available_definitions sig_type this_module_name this_module_name definitions {.#End}))))
(def: (imported_structs sig_type)
(-> Type (Meta (List [Name Type])))
@@ -175,16 +175,16 @@
accessible_definitions (monad.each ! meta.definitions imported_modules)]
(in (list\mix (function (_ [imported_module definitions] tail)
(available_definitions sig_type imported_module this_module_name definitions tail))
- #.End
+ {.#End}
(list.zipped/2 imported_modules accessible_definitions)))))
(def: (on_argument arg func)
(-> Type Type (Check Type))
(case func
- {#.Named _ func'}
+ {.#Named _ func'}
(on_argument arg func')
- {#.UnivQ _}
+ {.#UnivQ _}
(do check.monad
[[id var] check.var]
(|> func
@@ -192,7 +192,7 @@
maybe.trusted
(on_argument arg)))
- {#.Function input output}
+ {.#Function input output}
(do check.monad
[_ (check.check input arg)]
(in output))
@@ -203,11 +203,11 @@
(def: (concrete_type type)
(-> Type (Check [(List Nat) Type]))
(case type
- {#.UnivQ _}
+ {.#UnivQ _}
(do check.monad
[[id var] check.var
[ids final_output] (concrete_type (maybe.trusted (type.applied (list var) type)))]
- (in [{#.Item id ids}
+ (in [{.#Item id ids}
final_output]))
_
@@ -241,13 +241,13 @@
context' check.context
=deps (monad.each ! (provision compiler context') deps)]
(in =deps)))
- {#.Left error}
+ {.#Left error}
(list)
- {#.Right =deps}
+ {.#Right =deps}
(list [alt_name =deps]))))
list\conjoint)
- #.End
+ {.#End}
(meta.failure (format "No candidates for provisioning: " (%.type dep)))
found
@@ -260,15 +260,15 @@
(do meta.monad [alts (..local_env sig_type)] (..candidate_provision (provision sig_type) context dep alts))
(do meta.monad [alts (..local_structs sig_type)] (..candidate_provision (provision sig_type) context dep alts))
(do meta.monad [alts (..imported_structs sig_type)] (..candidate_provision (provision sig_type) context dep alts))))
- {#.Left error}
+ {.#Left error}
(check.failure error)
- {#.Right candidates}
+ {.#Right candidates}
(case candidates
- #.End
+ {.#End}
(check.failure (format "No candidates for provisioning: " (%.type dep)))
- {#.Item winner #.End}
+ {.#Item winner {.#End}}
(\ check.monad in winner)
_
@@ -292,13 +292,13 @@
context' check.context
=deps (monad.each ! (provision sig_type compiler context') deps)]
(in =deps)))
- {#.Left error}
+ {.#Left error}
(list)
- {#.Right =deps}
+ {.#Right =deps}
(list [alt_name =deps]))))
list\conjoint)
- #.End
+ {.#End}
(meta.failure (format "No alternatives for " (%.type (type.function input_types output_type))))
found
@@ -315,7 +315,7 @@
(def: (var? input)
(-> Code Bit)
(case input
- [_ {#.Identifier _}]
+ [_ {.#Identifier _}]
#1
_
@@ -328,7 +328,7 @@
(def: (instance$ [constructor dependencies])
(-> Instance Code)
(case dependencies
- #.End
+ {.#End}
(code.identifier constructor)
_
@@ -338,17 +338,17 @@
args (<>.or (<>.and (<>.some <code>.identifier) <code>.end!)
(<>.and (<>.some <code>.any) <code>.end!))])
(case args
- {#.Left [args _]}
+ {.#Left [args _]}
(do [! meta.monad]
[[member_idx sig_type] (..implicit_member member)
input_types (monad.each ! ..implicit_type args)
output_type meta.expected_type
chosen_ones (alternatives sig_type member_idx input_types output_type)]
(case chosen_ones
- #.End
+ {.#End}
(meta.failure (format "No implementation could be found for member: " (%.name member)))
- {#.Item chosen #.End}
+ {.#Item chosen {.#End}}
(in (list (` (\ (~ (instance$ chosen))
(~ (code.local_identifier (product.right member)))
(~+ (list\each code.identifier args))))))
@@ -360,7 +360,7 @@
(text.interposed ", "))
" --- for type: " (%.type sig_type)))))
- {#.Right [args _]}
+ {.#Right [args _]}
(do [! meta.monad]
[labels (|> (macro.identifier "") (list.repeated (list.size args)) (monad.all !))]
(in (list (` (let [(~+ (|> args (list.zipped/2 labels) (list\each ..pair_list) list\conjoint))]