aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library
diff options
context:
space:
mode:
authorEduardo Julian2022-07-27 21:46:33 -0400
committerEduardo Julian2022-07-27 21:46:33 -0400
commitebfe1bbbe543299f8691e4862fbc899637ff8cfd (patch)
tree21c8142deb052fd17ef85809429b2fa41048f45d /stdlib/source/library
parent5da753fb0a4e220ea29fb3f45c92a69358901c20 (diff)
New flat format for documentation fragments.
Diffstat (limited to 'stdlib/source/library')
-rw-r--r--stdlib/source/library/lux.lux56
-rw-r--r--stdlib/source/library/lux/documentation.lux134
2 files changed, 101 insertions, 89 deletions
diff --git a/stdlib/source/library/lux.lux b/stdlib/source/library/lux.lux
index be2a9eb33..6fb5b2a9f 100644
--- a/stdlib/source/library/lux.lux
+++ b/stdlib/source/library/lux.lux
@@ -1148,7 +1148,7 @@
{#End}}]}
_
- {#Left "Wrong syntax for All"}}
+ {#Left (wrong_syntax_error [..prelude "All"])}}
tokens)))
(def' .public Ex
@@ -1182,7 +1182,7 @@
{#End}}]}
_
- {#Left "Wrong syntax for Ex"}}
+ {#Left (wrong_syntax_error [..prelude "Ex"])}}
tokens)))
(def' .public ->
@@ -1196,7 +1196,7 @@
{#End}})
_
- (failure "Wrong syntax for ->")}
+ (failure (wrong_syntax_error [..prelude "->"]))}
(list#reversed tokens))))
(def' .public list
@@ -1370,11 +1370,11 @@
(meta#in (list (list#mix (function#flipped (right_associativity op)) first nexts)))
_
- (failure "Wrong syntax for left")}
+ (failure (wrong_syntax_error [..prelude "left"]))}
tokens')
_
- (failure "Wrong syntax for left")}
+ (failure (wrong_syntax_error [..prelude "left"]))}
tokens)))
(def' .public right
@@ -1385,11 +1385,11 @@
(meta#in (list (list#mix (right_associativity op) last prevs)))
_
- (failure "Wrong syntax for right")}
+ (failure (wrong_syntax_error [..prelude "right"]))}
(list#reversed tokens'))
_
- (failure "Wrong syntax for right")}
+ (failure (wrong_syntax_error [..prelude "right"]))}
tokens)))
(def' .public all Macro ..right)
@@ -1523,7 +1523,7 @@
test))))
_
- (failure "Wrong syntax for if")}
+ (failure (wrong_syntax_error [..prelude "if"]))}
tokens)))
(def' .private Property_List
@@ -2231,6 +2231,16 @@
(-> ($' List ($' List a)) ($' List a)))
(list#mix list#composite {#End} (list#reversed xs)))
+(def' .public symbol
+ Macro
+ (macro (_ tokens)
+ ({{#Item [_ {#Symbol [module name]}] {#End}}
+ (meta#in (list (tuple$ (list (text$ module) (text$ name)))))
+
+ _
+ (failure (..wrong_syntax_error [..prelude "symbol"]))}
+ tokens)))
+
(def' .public with_template
Macro
(macro (_ tokens)
@@ -2245,15 +2255,15 @@
(list#each (function#composite apply (replacement_environment bindings')))
list#conjoint
meta#in)
- (failure (..wrong_syntax_error [..prelude "with_template"]))))
+ (failure (..wrong_syntax_error (symbol ..with_template)))))
_
- (failure (..wrong_syntax_error [..prelude "with_template"]))}
+ (failure (..wrong_syntax_error (symbol ..with_template)))}
[(monad#each maybe#monad symbol_short bindings)
(monad#each maybe#monad tuple_list data)])
_
- (failure (..wrong_syntax_error [..prelude "with_template"]))}
+ (failure (..wrong_syntax_error (symbol ..with_template)))}
tokens)))
(def' .private (n// param subject)
@@ -2735,7 +2745,7 @@
(in (list (..quantified it))))))
_
- (failure (wrong_syntax_error [..prelude "type_literal"]))}
+ (failure (..wrong_syntax_error (symbol ..type_literal)))}
tokens)))
(def' .public is
@@ -2747,7 +2757,7 @@
(, value)))))
_
- (failure (wrong_syntax_error [..prelude "is"]))}
+ (failure (..wrong_syntax_error (symbol ..is)))}
tokens)))
(def' .public as
@@ -2759,7 +2769,7 @@
(, value)))))
_
- (failure (wrong_syntax_error [..prelude "as"]))}
+ (failure (..wrong_syntax_error (symbol ..as)))}
tokens)))
(def' .private (empty? xs)
@@ -2806,7 +2816,7 @@
actions))))
_
- (failure "Wrong syntax for exec")}
+ (failure (..wrong_syntax_error (symbol ..exec)))}
(list#reversed tokens))))
(def' .public Pattern
@@ -2873,7 +2883,7 @@
(in (list (` ((, (variant$ expansion)) (, value))))))
_
- (failure "Wrong syntax for case")}
+ (failure (..wrong_syntax_error (symbol ..case)))}
tokens)))
(def' .private pattern#or
@@ -2894,16 +2904,6 @@
_
(failure "Wrong syntax for pattern#or")))))
-(def' .public symbol
- Macro
- (macro (_ tokens)
- (case tokens
- (list [_ {#Symbol [module name]}])
- (meta#in (list (` [(, (text$ module)) (, (text$ name))])))
-
- _
- (failure (..wrong_syntax_error [..prelude "symbol"])))))
-
(def' .private (symbol? code)
(type_literal (-> Code Bit))
(case code
@@ -4553,7 +4553,9 @@
(in referral)
_
- (failure (all text#composite "Wrong syntax for refer @ " current_module
+ (failure (all text#composite
+ (..wrong_syntax_error (symbol ..refer))
+ \n "@ " current_module
\n (|> extra
(list#each code#encoded)
(list#interposed " ")
diff --git a/stdlib/source/library/lux/documentation.lux b/stdlib/source/library/lux/documentation.lux
index cf2aa5adc..d2052c074 100644
--- a/stdlib/source/library/lux/documentation.lux
+++ b/stdlib/source/library/lux/documentation.lux
@@ -15,13 +15,15 @@
[collection
["[0]" list (.use "[1]#[0]" monad mix monoid)]
["[0]" set (.only Set)]
- ["[0]" stream (.only Stream)]]
+ ["[0]" stream (.only Stream)]
+ ["[0]" dictionary (.only Dictionary)]]
[format
["md" markdown (.only Markdown Block)]]]
[math
[number
["n" nat]]]
["[0]" meta (.only)
+ ["[0]" symbol]
["[0]" type (.use "[1]#[0]" equivalence)]
["[0]" code (.only)
["<[1]>" \\parser (.only Parser)]]
@@ -134,7 +136,6 @@
Text
(format \n \n))
-
(def (fragment_documentation module fragment)
(-> Text Fragment Text)
(case fragment
@@ -148,20 +149,9 @@
(..code_documentation module (has .#column reference_column location) reference_column)
product.right))))
-(def parameter_name_options "abcdefghijklmnopqrstuvwxyz")
-(def parameter_name_options_count (text.size parameter_name_options))
-
-(def (parameter_type_name id)
+(def parameter_type_name
(-> Nat Text)
- (format "_" (%.nat id))
- ... (case (text.char id ..parameter_name_options)
- ... {.#Some char}
- ... (text.of_char char)
-
- ... {.#None}
- ... (format (parameter_type_name (n./ parameter_name_options_count id))
- ... (parameter_type_name (n.% parameter_name_options_count id))))
- )
+ (|>> %.nat (format "_")))
(def type_variable_names
(Stream Text)
@@ -565,15 +555,19 @@
(.type .public Definition
(Record
- [#definition Text
+ [#global Symbol
#documentation (Markdown Block)]))
(.type .public Module
(Record
[#module Text
#description Text
- #expected (Set Text)
- #definitions (List Definition)]))
+ #coverage (Set Text)]))
+
+(.type .public Documentation
+ (Variant
+ {#Definition Definition}
+ {#Module Module}))
(def .public definition
(syntax (_ [[name parameters] ..declaration
@@ -589,53 +583,46 @@
(,* (list#each code.local parameters)))
(,* extra))))]
(macro.with_symbols [g!_]
- (let [[_ short] name]
- (in (list (` (.let [(, g!_) (.is (.-> .Any (.List ..Definition))
+ (let [[module short] name]
+ (in (list (` (.let [(, g!_) (.is (.-> .Any ..Documentation)
(.function ((, g!_) (, g!_))
- (.list [..#definition (, (code.text short))
- ..#documentation (,* documentation)])))]
+ {#Definition [..#global [(, (code.text module)) (, (code.text short))]
+ ..#documentation (,* documentation)]}))]
((, g!_) []))))))))))
(def definitions_documentation
(-> (List Definition) (Markdown Block))
(|>> (list.sorted (function (_ left right)
- (text#< (the #definition right)
- (the #definition left))))
+ (text#< (symbol.short (the #global right))
+ (symbol.short (the #global left)))))
(list#each (the #documentation))
(list#mix md.then md.empty)))
-(def expected_separator
+(def coverage_separator
Text
(text.of_char 31))
-(def expected_format
+(def coverage_format
(-> (List Text) Text)
(list#mix (function (_ short aggregate)
(case aggregate
"" short
- _ (format aggregate ..expected_separator short)))
+ _ (format aggregate ..coverage_separator short)))
""))
(`` (def .public module
(syntax (_ [[name _] ..qualified_symbol
- description <code>.any
- definitions (<code>.tuple (<>.some <code>.any))
- subs (<code>.tuple (<>.some <code>.any))])
+ description <code>.any])
(do meta.monad
- [expected (meta.exports name)]
- (in (list (` (is (List Module)
- (list.partial [..#module (, (code.text name))
- ..#description (, description)
- ..#expected (|> (, (code.text (|> expected
- (list#each product.left)
- ..expected_format)))
- (text.all_split_by (,, (static ..expected_separator)))
- (set.of_list text.hash))
- ..#definitions (list.together (list (,* definitions)))]
- (all (at list.monoid (,' composite))
- (is (List Module)
- (at list.monoid (,' identity)))
- (,* subs)))))))))))
+ [coverage (meta.exports name)]
+ (in (list (` (is Documentation
+ {#Module [..#module (, (code.text name))
+ ..#description (, description)
+ ..#coverage (|> (, (code.text (|> coverage
+ (list#each product.left)
+ ..coverage_format)))
+ (text.all_split_by (,, (static ..coverage_separator)))
+ (set.of_list text.hash))]}))))))))
(def listing
(-> (List Text) (Markdown Block))
@@ -645,31 +632,33 @@
{.#None}]))
md.numbered_list))
-(def (module_documentation module)
- (-> Module (Markdown Block))
+(def (module_documentation [module definitions])
+ (-> [Module (List Definition)] (Markdown Block))
(let [(open "_[0]") module]
(all md.then
... Name
(md.heading/1 (the #module module))
+
... Description
(case (the #description module)
"" md.empty
description (<| md.paragraph
md.text
description))
+
... Definitions
(md.heading/2 "Definitions")
- (|> module
- (the #definitions)
- (list.only (|>> (the #definition)
- (set.member? _#expected)))
+ (|> definitions
+ (list.only (|>> (the #global)
+ symbol.short
+ (set.member? _#coverage)))
..definitions_documentation)
+
... Missing documentation
- (case (|> module
- (the #definitions)
+ (case (|> definitions
(list#mix (function (_ definition missing)
- (set.lacks (the #definition definition) missing))
- _#expected)
+ (set.lacks (symbol.short (the #global definition)) missing))
+ _#coverage)
set.list)
{.#End}
md.empty
@@ -678,13 +667,15 @@
(all md.then
(md.heading/2 "Missing documentation")
(..listing missing)))
+
... Un-expected documentation
- (case (|> module
- (the #definitions)
- (list.only (|>> (the #definition)
- (set.member? _#expected)
+ (case (|> definitions
+ (list.only (|>> (the #global)
+ symbol.short
+ (set.member? _#coverage)
not))
- (list#each (the #definition)))
+ (list#each (|>> (the #global)
+ symbol.short)))
{.#End}
md.empty
@@ -695,9 +686,28 @@
)))
(def .public markdown
- (-> (List Module) Text)
- (|>> (list.sorted (function (_ left right)
- (text#< (the #module right) (the #module left))))
+ (-> (List Documentation) Text)
+ (|>> (list#mix (function (_ doc it)
+ (case doc
+ {#Module doc}
+ (if (dictionary.key? it (the #module doc))
+ it
+ (dictionary.has (the #module doc) [doc (list)] it))
+
+ {#Definition doc}
+ (let [module (symbol.module (the #global doc))]
+ (if (dictionary.key? it module)
+ (dictionary.revised module
+ (function (_ [module defs])
+ [module (list.partial doc defs)])
+ it)
+ it))))
+ (is (Dictionary Text [Module (List Definition)])
+ (dictionary.empty text.hash)))
+ dictionary.values
+ (list.sorted (function (_ left right)
+ (text#< (the #module (product.left right))
+ (the #module (product.left left)))))
(list#each ..module_documentation)
(list.interposed md.horizontal_rule)
(list#mix md.then (is (Markdown Block) md.empty))