diff options
Diffstat (limited to 'stdlib/source/library')
23 files changed, 111 insertions, 148 deletions
diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux index 50fe70f4e..986378ad7 100644 --- a/stdlib/source/library/lux.lux +++ b/stdlib/source/library/lux.lux @@ -3937,7 +3937,7 @@ (in_meta [#All tokens']) (^or (^ (list& [_ (#Tag ["" "_"])] tokens')) - (^ (list& [_ (#Tag ["" "nothing"])] tokens'))) + (^ (list& [_ (#Tag ["" "ignore"])] tokens'))) (in_meta [#Ignore tokens']) _ diff --git a/stdlib/source/library/lux/data/text.lux b/stdlib/source/library/lux/data/text.lux index 096c25a9a..70b0360b1 100644 --- a/stdlib/source/library/lux/data/text.lux +++ b/stdlib/source/library/lux/data/text.lux @@ -20,7 +20,6 @@ ["." i64]]]]]) (type: .public Char - {#.doc (example "A character code number.")} Nat) ... TODO: Instead of ints, chars should be produced fron nats. @@ -45,7 +44,6 @@ ) (def: .public line_feed - {#.doc (example "Same as 'new_line'.")} ..new_line) (def: .public size @@ -53,7 +51,6 @@ (|>> "lux text size")) (def: .public (char index input) - {#.doc (example "Yields the character at the specified index.")} (-> Nat Text (Maybe Char)) (if (n.< ("lux text size" input) index) (#.Some ("lux text char" index input)) @@ -126,12 +123,10 @@ ("lux text concat" subject param)) (def: .public (enclosed [left right] content) - {#.doc "Surrounds the given content text with left and right side additions."} (-> [Text Text] Text Text) ($_ "lux text concat" left content right)) (def: .public (enclosed' boundary content) - {#.doc "Surrounds the given content text with the same boundary text."} (-> Text Text Text) (enclosed [boundary boundary] content)) @@ -140,14 +135,12 @@ (..enclosed' ..double_quote)) (def: .public (clip offset size input) - {#.doc (example "Clips a chunk of text from the input at the specified offset and of the specified size.")} (-> Nat Nat Text (Maybe Text)) (if (|> size (n.+ offset) (n.<= ("lux text size" input))) (#.Some ("lux text clip" offset size input)) #.None)) (def: .public (clip' offset input) - {#.doc (example "Clips the remaining text from the input at the specified offset.")} (-> Nat Text (Maybe Text)) (let [size ("lux text size" input)] (if (n.<= size offset) @@ -314,7 +307,6 @@ " ") (def: .public (space? char) - {#.doc "Checks whether the character is white-space."} (-> Char Bit) (with_expansions [<options> (template [<char>] [(^ (.char (~~ (static <char>))))] diff --git a/stdlib/source/library/lux/documentation.lux b/stdlib/source/library/lux/documentation.lux index 37147b2f0..aca2b4e89 100644 --- a/stdlib/source/library/lux/documentation.lux +++ b/stdlib/source/library/lux/documentation.lux @@ -258,20 +258,20 @@ (syntax: .public (default [name ..qualified_identifier]) (let [[_ short] name] - (in (list (` (: ..Definition - {#..definition (~ (code.text short)) - #..documentation ((~! ..minimal_definition_documentation) - (~ (code.identifier name)))})))))) + (in (list (` (: (.List ..Definition) + (list {#..definition (~ (code.text short)) + #..documentation ((~! ..minimal_definition_documentation) + (~ (code.identifier name)))}))))))) (syntax: .public (documentation: [name ..qualified_identifier extra (<>.some <code>.any)]) (let [[_ short] name] (in (list (` (.def: .public (~ (code.local_identifier short)) - ..Definition - {#..definition (~ (code.text short)) - #..documentation ((~! ..definition_documentation) - (~ (code.identifier name)) - (~+ extra))})))))) + (.List ..Definition) + (.list {#..definition (~ (code.text short)) + #..documentation ((~! ..definition_documentation) + (~ (code.identifier name)) + (~+ extra))}))))))) (def: definitions_documentation (-> (List Definition) (Markdown Block)) @@ -318,7 +318,7 @@ (~ (code.text (|> expected (list\map product.left) ..expected_format))) - (list (~+ definitions))) + ((~! list.together) (list (~+ definitions)))) ($_ (\ (~! list.monoid) (~' compose)) (: (List Module) (\ (~! list.monoid) (~' identity))) diff --git a/stdlib/source/library/lux/locale.lux b/stdlib/source/library/lux/locale.lux index 5ff8380b5..39befd846 100644 --- a/stdlib/source/library/lux/locale.lux +++ b/stdlib/source/library/lux/locale.lux @@ -17,7 +17,7 @@ ["." territory (#+ Territory)]]) (abstract: .public Locale - {#.doc (example "A description of a locale; with territory, (optional) language, and (optional) text-encoding.")} + {} Text diff --git a/stdlib/source/library/lux/locale/language.lux b/stdlib/source/library/lux/locale/language.lux index 29ec7c190..1739135aa 100644 --- a/stdlib/source/library/lux/locale/language.lux +++ b/stdlib/source/library/lux/locale/language.lux @@ -13,7 +13,7 @@ ... https://en.wikipedia.org/wiki/List_of_ISO_639-2_codes (abstract: .public Language - {#.doc (example "An ISO 639 language.")} + {} {#name Text #code Text} diff --git a/stdlib/source/library/lux/locale/territory.lux b/stdlib/source/library/lux/locale/territory.lux index 6309e1a86..c4172993a 100644 --- a/stdlib/source/library/lux/locale/territory.lux +++ b/stdlib/source/library/lux/locale/territory.lux @@ -13,7 +13,7 @@ ... https://en.wikipedia.org/wiki/ISO_3166-1 (abstract: .public Territory - {#.doc (example "An ISO 3166 territory.")} + {} {#name Text #short Text diff --git a/stdlib/source/library/lux/macro.lux b/stdlib/source/library/lux/macro.lux index f6e2e1716..8e11c4a58 100644 --- a/stdlib/source/library/lux/macro.lux +++ b/stdlib/source/library/lux/macro.lux @@ -19,8 +19,6 @@ ["." location]]]) (def: .public (single_expansion syntax) - {#.doc (example "Given code that requires applying a macro, does it once and returns the result." - "Otherwise, returns the code as-is.")} (-> Code (Meta (List Code))) (case syntax [_ (#.Form (#.Item [[_ (#.Identifier name)] args]))] @@ -37,8 +35,6 @@ (\ //.monad in (list syntax)))) (def: .public (expansion syntax) - {#.doc (example "Given code that requires applying a macro, expands repeatedly until no more direct macro-calls are left." - "Otherwise, returns the code as-is.")} (-> Code (Meta (List Code))) (case syntax [_ (#.Form (#.Item [[_ (#.Identifier name)] args]))] @@ -59,7 +55,6 @@ (\ //.monad in (list syntax)))) (def: .public (full_expansion syntax) - {#.doc "Expands all macro-calls everywhere recursively, until only primitive/base code remains."} (-> Code (Meta (List Code))) (case syntax [_ (#.Form (#.Item [[_ (#.Identifier name)] args]))] @@ -107,8 +102,6 @@ (\ //.monad in (list syntax)))) (def: .public (identifier prefix) - {#.doc (example "Generates a unique name as an Code node (ready to be used in code templates)." - "A prefix can be given (or just be empty text) to better identify the code for debugging purposes.")} (-> Text (Meta Code)) (do //.monad [id //.seed] @@ -127,23 +120,12 @@ (//.failure (text\compose "Code is not a local identifier: " (code.format ast))))) (def: .public wrong_syntax_error - {#.doc (example "A generic error message for macro syntax failures.")} (-> Name Text) (|>> name\encode (text.prefix (text\compose "Wrong syntax for " text.\'')) (text.suffix (text\compose text.\'' ".")))) (macro: .public (with_identifiers tokens) - {#.doc (example "Creates new identifiers and offers them to the body expression." - (syntax: .public (synchronized [lock any - body any]) - (with_identifiers [g!lock g!body g!_] - (in (list (` (let [(~ g!lock) (~ lock) - (~ g!_) ("jvm monitorenter" (~ g!lock)) - (~ g!body) (~ body) - (~ g!_) ("jvm monitorexit" (~ g!lock))] - (~ g!body))))) - )))} (case tokens (^ (list [_ (#.Tuple identifiers)] body)) (do {! //.monad} @@ -159,7 +141,6 @@ (//.failure (..wrong_syntax_error (name_of ..with_identifiers))))) (def: .public (one_expansion token) - {#.doc "Works just like expand, except that it ensures that the output is a single Code token."} (-> Code (Meta Code)) (do //.monad [token+ (..expansion token)] @@ -172,13 +153,6 @@ (template [<macro> <func>] [(macro: .public (<macro> tokens) - {#.doc (example "Performs a macro-expansion and logs the resulting code." - "You can either use the resulting code, or omit them." - "By omitting them, this macro produces nothing (just like the lux.comment macro)." - (<macro> #omit - (def: (foo bar baz) - (-> Int Int Int) - (int.+ bar baz))))} (let [[module _] (name_of .._) [_ short] (name_of <macro>) macro_name [module short]] diff --git a/stdlib/source/library/lux/macro/code.lux b/stdlib/source/library/lux/macro/code.lux index 7e09ceb96..79eebb5df 100644 --- a/stdlib/source/library/lux/macro/code.lux +++ b/stdlib/source/library/lux/macro/code.lux @@ -53,14 +53,13 @@ [record (List [Code Code]) #.Record] ) -(template [<name> <tag> <doc>] +(template [<name> <tag>] [(def: .public (<name> name) - {#.doc <doc>} (-> Text Code) [location.dummy (<tag> ["" name])])] - [local_identifier #.Identifier "Produces a local identifier (an identifier with no module prefix)."] - [local_tag #.Tag "Produces a local tag (a tag with no module prefix)."]) + [local_identifier #.Identifier] + [local_tag #.Tag]) (implementation: .public equivalence (Equivalence Code) diff --git a/stdlib/source/library/lux/macro/local.lux b/stdlib/source/library/lux/macro/local.lux index 8c518b855..d17ae7728 100644 --- a/stdlib/source/library/lux/macro/local.lux +++ b/stdlib/source/library/lux/macro/local.lux @@ -96,10 +96,6 @@ (list))))))) (def: .public (push macros) - {#.doc (example "Installs macros in the compiler-state, with the given names." - "Yields code that can be placed either as expression or as directives." - "This code un-installs the macros." - "NOTE: Always use this code once to clean-up..")} (-> (List [Name Macro]) (Meta Code)) (do meta.monad [_ (monad.map meta.monad ..push_one macros) diff --git a/stdlib/source/library/lux/macro/syntax.lux b/stdlib/source/library/lux/macro/syntax.lux index cdb788bc9..4caed5bd7 100644 --- a/stdlib/source/library/lux/macro/syntax.lux +++ b/stdlib/source/library/lux/macro/syntax.lux @@ -42,22 +42,6 @@ (#.Item [[x y] pairs']) (list& x y (un_paired pairs')))) (macro: .public (syntax: tokens) - {#.doc (example "A more advanced way to define macros than 'macro:'." - "The inputs to the macro can be parsed in complex ways through the use of syntax parsers." - "The macro body is also (implicitly) run in the Meta monad, to save some typing." - "Also, the compiler state can be accessed through the *lux* binding." - (syntax: .public (object [.let [imports (class_imports *lux*)] - .let [class_vars (list)] - super (opt (super_class_decl^ imports class_vars)) - interfaces (tuple (some (super_class_decl^ imports class_vars))) - constructor_args (constructor_args^ imports class_vars) - methods (some (overriden_method_def^ imports))]) - (let [def_code ($_ text\compose "anon-class:" - (spaced (list (super_class_decl$ (maybe.else object_super_class super)) - (with_brackets (spaced (list\map super_class_decl$ interfaces))) - (with_brackets (spaced (list\map constructor_arg$ constructor_args))) - (with_brackets (spaced (list\map (method_def$ id) methods))))))] - (in (list (` ((~ (code.text def_code)))))))))} (let [?parts (: (Maybe [Code Text (List Code) Code Code]) (case tokens (^ (list export_policy diff --git a/stdlib/source/library/lux/macro/syntax/annotations.lux b/stdlib/source/library/lux/macro/syntax/annotations.lux index 5e23ea9d8..29ef222c2 100644 --- a/stdlib/source/library/lux/macro/syntax/annotations.lux +++ b/stdlib/source/library/lux/macro/syntax/annotations.lux @@ -16,7 +16,6 @@ ["." code]]]]) (type: .public Annotations - {#.doc (example "Definition/module annotations.")} (List [Name Code])) (def: .public equivalence diff --git a/stdlib/source/library/lux/macro/syntax/check.lux b/stdlib/source/library/lux/macro/syntax/check.lux index 26450894a..8c045da18 100644 --- a/stdlib/source/library/lux/macro/syntax/check.lux +++ b/stdlib/source/library/lux/macro/syntax/check.lux @@ -18,7 +18,6 @@ "lux check") (type: .public Check - {#.doc (example "A type annotation for an expression.")} {#type Code #value Code}) diff --git a/stdlib/source/library/lux/macro/syntax/declaration.lux b/stdlib/source/library/lux/macro/syntax/declaration.lux index 1a529d3db..004398916 100644 --- a/stdlib/source/library/lux/macro/syntax/declaration.lux +++ b/stdlib/source/library/lux/macro/syntax/declaration.lux @@ -15,7 +15,6 @@ ["." code]]]]) (type: .public Declaration - {#.doc (example "A declaration for either a constant or a function.")} {#name Text #arguments (List Text)}) @@ -27,10 +26,6 @@ )) (def: .public parser - {#.doc (example "A parser for declaration syntax." - "Such as:" - quux - (foo bar baz))} (Parser Declaration) (<>.either (<>.and <code>.local_identifier (<>\in (list))) diff --git a/stdlib/source/library/lux/macro/syntax/definition.lux b/stdlib/source/library/lux/macro/syntax/definition.lux index 79fde60e7..601f44283 100644 --- a/stdlib/source/library/lux/macro/syntax/definition.lux +++ b/stdlib/source/library/lux/macro/syntax/definition.lux @@ -26,7 +26,6 @@ ["#." check (#+ Check)]]) (type: .public Definition - {#.doc (example "Syntax for a constant definition.")} {#name Text #value (Either Check Code) @@ -101,7 +100,6 @@ )))) (def: .public (parser compiler) - {#.doc "A reader that first macro-expands and then analyses the input Code, to ensure it is a definition."} (-> Lux (Parser Definition)) (do {! <>.monad} [raw <code>.any @@ -129,7 +127,6 @@ ["Definition" (%.code (..format definition))])) (def: .public (typed compiler) - {#.doc "Only works for typed definitions."} (-> Lux (Parser Definition)) (do <>.monad [definition (..parser compiler) diff --git a/stdlib/source/library/lux/macro/syntax/export.lux b/stdlib/source/library/lux/macro/syntax/export.lux index 077e36256..e4cb2ddac 100644 --- a/stdlib/source/library/lux/macro/syntax/export.lux +++ b/stdlib/source/library/lux/macro/syntax/export.lux @@ -1,5 +1,4 @@ (.module: - {#.doc (.example "Syntax for marking a definition as an export.")} [library [lux #* [control diff --git a/stdlib/source/library/lux/macro/syntax/input.lux b/stdlib/source/library/lux/macro/syntax/input.lux index 77623fbd7..58675bbf7 100644 --- a/stdlib/source/library/lux/macro/syntax/input.lux +++ b/stdlib/source/library/lux/macro/syntax/input.lux @@ -12,7 +12,6 @@ ["." code]]]]) (type: .public Input - {#.doc (example "The common typed-argument syntax used by many macros.")} {#binding Code #type Code}) @@ -30,7 +29,6 @@ (value@ #type value)]))) (def: .public parser - {#.doc "Parser for the common typed-argument syntax used by many macros."} (Parser Input) (<code>.record ($_ <>.and diff --git a/stdlib/source/library/lux/macro/syntax/type/variable.lux b/stdlib/source/library/lux/macro/syntax/type/variable.lux index 9f69dfbe0..7e66ca622 100644 --- a/stdlib/source/library/lux/macro/syntax/type/variable.lux +++ b/stdlib/source/library/lux/macro/syntax/type/variable.lux @@ -12,7 +12,6 @@ ["." code]]]]) (type: .public Variable - {#.doc (example "A variable'S name.")} Text) (def: .public equivalence @@ -24,6 +23,5 @@ code.local_identifier) (def: .public parser - {#.doc "Parser for the common type variable/parameter used by many macros."} (Parser Variable) <code>.local_identifier) diff --git a/stdlib/source/library/lux/macro/template.lux b/stdlib/source/library/lux/macro/template.lux index d378f9409..aac7af03c 100644 --- a/stdlib/source/library/lux/macro/template.lux +++ b/stdlib/source/library/lux/macro/template.lux @@ -35,12 +35,6 @@ (syntax: .public (with_locals [locals (<code>.tuple (<>.some <code>.local_identifier)) body <code>.any]) - {#.doc (example "Creates names for local bindings aliased by the names you choose." - (with_locals [my_var] - (let [my_var 123] - (..text [my_var]))) - "=>" - "__gensym__my_var506")} (do {! meta.monad} [g!locals (|> locals (list\map //.identifier) @@ -87,38 +81,21 @@ (<code>.tuple (<>.many (..snippet module_side?)))) (syntax: .public (text [simple (..part false)]) - {#.doc (example "A text literal made by concatenating pieces of code." - (text [#0 123 +456 +789.0 "abc" .def ..ghi]) - "=>" - "#0123+456+789.0abcdefghi")} (in (list (|> simple (text.interposed "") code.text)))) -(template [<a/an> <name> <simple> <complex> <short_example> <full_example>] - [(`` (syntax: .public (<name> [name (<>.or (<>.and (..part true) (..part false)) - (..part false))]) - {#.doc (example (~~ (..text [<a/an> " " <name> " made by concatenating pieces of code."])) - "The (optional) module part and the short part are specified independently." - (<name> ["abc" .def ..ghi]) - "=>" - <short_example> - "--------------" - (<name> [.def] ["abc" .def ..ghi]) - "=>" - <full_example>)} - (case name - (#.Left [simple complex]) - (in (list (<complex> [(text.interposed "" simple) - (text.interposed "" complex)]))) - - (#.Right simple) - (in (list (|> simple (text.interposed "") <simple>))))))] - - ["An" identifier code.local_identifier code.identifier - abcdefghi - .abcdefghi] - ["A" tag code.local_tag code.tag - #abcdefghi - #.abcdefghi] +(template [<name> <simple> <complex>] + [(syntax: .public (<name> [name (<>.or (<>.and (..part true) (..part false)) + (..part false))]) + (case name + (#.Left [simple complex]) + (in (list (<complex> [(text.interposed "" simple) + (text.interposed "" complex)]))) + + (#.Right simple) + (in (list (|> simple (text.interposed "") <simple>)))))] + + [identifier code.local_identifier code.identifier] + [tag code.local_tag code.tag] ) (type: Environment @@ -186,12 +163,6 @@ (syntax: .public (let [locals (<code>.tuple (<>.some ..local)) body <code>.any]) - {#.doc (example "Lexically-bound templates." - (let [(!square <root>) - [(nat.* <root> <root>)]] - (def: (square root) - (-> Nat Nat) - (!square root))))} (do meta.monad [here_name meta.current_module_name expression? (: (Meta Bit) diff --git a/stdlib/source/library/lux/math/infix.lux b/stdlib/source/library/lux/math/infix.lux index 12611788f..f63e86a4d 100644 --- a/stdlib/source/library/lux/math/infix.lux +++ b/stdlib/source/library/lux/math/infix.lux @@ -1,5 +1,4 @@ (.module: - {#.doc "Common mathematical constants and functions."} [library [lux #* [abstract @@ -85,16 +84,4 @@ (` ((~ op) (~ (prefix right)) (~ (prefix left)))))) (syntax: .public (infix [expr ..expression]) - {#.doc (example "Infix math syntax." - (infix [x i.* +10]) - (infix [[x i.+ y] i.* [x i.- y]]) - (infix [sin [x i.+ y]]) - (infix [[x n.< y] and [y n.< z]]) - (infix [#and x n.< y n.< z]) - (infix [(n.* 3 9) gcd 450]) - - "The rules for infix syntax are simple." - "If you want your binary function to work well with it." - "Then take the argument to the right (y) as your first argument," - "and take the argument to the left (x) as your second argument.")} (in (list (..prefix expr)))) diff --git a/stdlib/source/library/lux/math/logic/continuous.lux b/stdlib/source/library/lux/math/logic/continuous.lux index cffcc4e5d..6f7e4d116 100644 --- a/stdlib/source/library/lux/math/logic/continuous.lux +++ b/stdlib/source/library/lux/math/logic/continuous.lux @@ -1,8 +1,5 @@ ... https://en.wikipedia.org/wiki/Many-valued_logic (.module: - {#.doc (.example "Continuous logic using Rev values." - "Continuous logic is logic in the interval [0,1] instead of just the binary #0 and #1 options." - "Because Rev is being used, the interval is actual [0,1).")} [library [lux (#- false true or and not) [abstract diff --git a/stdlib/source/library/lux/math/logic/fuzzy.lux b/stdlib/source/library/lux/math/logic/fuzzy.lux index 843af83ad..5a21a6e39 100644 --- a/stdlib/source/library/lux/math/logic/fuzzy.lux +++ b/stdlib/source/library/lux/math/logic/fuzzy.lux @@ -1,6 +1,5 @@ ... https://en.wikipedia.org/wiki/Fuzzy_logic (.module: - {#.doc "Fuzzy logic, implemented on top of the Rev type."} [library [lux #* [abstract @@ -18,7 +17,6 @@ ["#" continuous]]) (type: .public (Fuzzy a) - {#.doc (example "A fuzzy set.")} (-> a Rev)) (implementation: .public functor diff --git a/stdlib/source/library/lux/static.lux b/stdlib/source/library/lux/static.lux new file mode 100644 index 000000000..0a506ef2d --- /dev/null +++ b/stdlib/source/library/lux/static.lux @@ -0,0 +1,71 @@ +(.module: + [library + [lux (#- nat int rev) + ["." meta] + [abstract + [monad (#+ do)]] + [control + ["<>" parser + ["<.>" code]]] + [macro + [syntax (#+ syntax:)] + ["." code]] + [math + [number (#+ hex)] + ["." random (#+ Random)]]]]) + +(template [<name> <type> <format>] + [(syntax: .public (<name> [expression <code>.any]) + (\ meta.monad map + (|>> (:as <type>) <format> list) + (meta.eval <type> expression)))] + + [nat .Nat code.nat] + [int .Int code.int] + [rev .Rev code.rev] + [frac .Frac code.frac] + [text .Text code.text] + ) + +(def: pcg_32_magic_inc + Nat + (hex "FEDCBA9876543210")) + +(with_expansions [<type> (Ex [a] + [(-> a Code) + a])] + (syntax: .public (literal [format <code>.any + expression <code>.any]) + (do meta.monad + [pair (meta.eval (type <type>) + (` [(~ format) (~ expression)])) + .let [[format expression] (:as <type> pair)]] + (in (list (format expression)))))) + +(template [<name> <random> <format>] + [(syntax: .public (<name> []) + (do meta.monad + [seed meta.seed + .let [[_ result] (random.result (random.pcg_32 [..pcg_32_magic_inc seed]) + <random>)]] + (in (list (<format> result)))))] + + [random_nat random.nat code.nat] + [random_int random.int code.int] + [random_rev random.rev code.rev] + [random_frac random.frac code.frac] + ) + +(with_expansions [<type> (Ex [a] + [(-> a Code) + (Random a)])] + (syntax: .public (random [format <code>.any + random <code>.any]) + (do meta.monad + [pair (meta.eval (type <type>) + (` [(~ format) (~ random)])) + .let [[format random] (:as <type> pair)] + seed meta.seed + .let [[_ result] (random.result (random.pcg_32 [..pcg_32_magic_inc seed]) + random)]] + (in (list (format result)))))) diff --git a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux index 329c79611..c5f410370 100644 --- a/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux +++ b/stdlib/source/library/lux/tool/compiler/language/lux/phase/extension/directive/lux.lux @@ -236,6 +236,14 @@ _ (phase.except ///.invalid_syntax [extension_name %.code inputsC+])))) +(def: (announce_tags! tags owner) + (All [anchor expression directive] + (-> (List Text) Type (Operation anchor expression directive (List Any)))) + (/////directive.lifted_generation + (monad.map phase.monad (function (_ tag) + (/////generation.log! (format "#" tag " : Tag of " (%.type owner)))) + tags))) + (def: (def::type_tagged expander host_analysis) (-> Expander /////analysis.Bundle Handler) (..custom @@ -255,7 +263,8 @@ [_ (module.define short_name (#.Right [exported? type annotations value]))] (module.declare_tags tags exported? (:as Type value)))) _ (..refresh expander host_analysis) - _ (..announce_definition! short_name type)] + _ (..announce_definition! short_name type) + _ (..announce_tags! tags (:as Type value))] (in /////directive.no_requirements)))])) (def: imports |