aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/documentation
diff options
context:
space:
mode:
authorEduardo Julian2022-07-06 16:25:43 -0400
committerEduardo Julian2022-07-06 16:25:43 -0400
commit5270f301eba5237feebc8eca14aee6b7a992a819 (patch)
treea1adb545189f4db807d712a1fcc7d20048c11222 /stdlib/source/documentation
parent0c32c7f03ad1f8f0db54b623dc407713bbf8cacd (diff)
Made exception.report a function.
Diffstat (limited to 'stdlib/source/documentation')
-rw-r--r--stdlib/source/documentation/lux.lux2
-rw-r--r--stdlib/source/documentation/lux/control/exception.lux8
-rw-r--r--stdlib/source/documentation/lux/control/parser.lux20
-rw-r--r--stdlib/source/documentation/lux/control/parser/cli.lux57
-rw-r--r--stdlib/source/documentation/lux/control/parser/code.lux115
-rw-r--r--stdlib/source/documentation/lux/control/parser/environment.lux43
-rw-r--r--stdlib/source/documentation/lux/control/parser/type.lux141
-rw-r--r--stdlib/source/documentation/lux/meta.lux29
-rw-r--r--stdlib/source/documentation/lux/meta/code.lux81
-rw-r--r--stdlib/source/documentation/lux/meta/compiler/language/lux/analysis.lux (renamed from stdlib/source/documentation/lux/tool/compiler/language/lux/analysis.lux)0
-rw-r--r--stdlib/source/documentation/lux/meta/compiler/language/lux/declaration.lux (renamed from stdlib/source/documentation/lux/tool/compiler/language/lux/declaration.lux)0
-rw-r--r--stdlib/source/documentation/lux/meta/compiler/language/lux/generation.lux (renamed from stdlib/source/documentation/lux/tool/compiler/language/lux/generation.lux)0
-rw-r--r--stdlib/source/documentation/lux/meta/compiler/language/lux/synthesis.lux (renamed from stdlib/source/documentation/lux/tool/compiler/language/lux/synthesis.lux)0
-rw-r--r--stdlib/source/documentation/lux/meta/compiler/phase.lux (renamed from stdlib/source/documentation/lux/tool/compiler/phase.lux)0
-rw-r--r--stdlib/source/documentation/lux/meta/type.lux114
-rw-r--r--stdlib/source/documentation/lux/program.lux41
-rw-r--r--stdlib/source/documentation/lux/tool.lux19
-rw-r--r--stdlib/source/documentation/lux/world/environment.lux31
18 files changed, 291 insertions, 410 deletions
diff --git a/stdlib/source/documentation/lux.lux b/stdlib/source/documentation/lux.lux
index 6e008a209..578bee850 100644
--- a/stdlib/source/documentation/lux.lux
+++ b/stdlib/source/documentation/lux.lux
@@ -29,7 +29,6 @@
["[1][0]" static]
["[1][0]" test]
["[1][0]" time]
- ["[1][0]" tool] ... TODO: Documentation for this
["[1][0]" world]])
(.`` (.def .public documentation
@@ -900,7 +899,6 @@
/static.documentation
/test.documentation
/time.documentation
- /tool.documentation
/world.documentation])))
(program: inputs
diff --git a/stdlib/source/documentation/lux/control/exception.lux b/stdlib/source/documentation/lux/control/exception.lux
index 01cecf3ea..14db6b941 100644
--- a/stdlib/source/documentation/lux/control/exception.lux
+++ b/stdlib/source/documentation/lux/control/exception.lux
@@ -51,10 +51,10 @@
($.documentation /.report
"An error report."
[(is Text
- (report ["Row 0" value/0]
- ["Row 1" value/1]
- ,,,
- ["Row N" value/N]))])
+ (report (list ["Row 0" value/0]
+ ["Row 1" value/1]
+ ,,,
+ ["Row N" value/N])))])
($.documentation /.listing
(format "A numbered report of the entries on a list."
diff --git a/stdlib/source/documentation/lux/control/parser.lux b/stdlib/source/documentation/lux/control/parser.lux
index ac253916e..4d2389f71 100644
--- a/stdlib/source/documentation/lux/control/parser.lux
+++ b/stdlib/source/documentation/lux/control/parser.lux
@@ -6,16 +6,7 @@
[text (.only \n)
["%" \\format (.only format)]]]]]
[\\library
- ["[0]" /]]
- ["[0]" /
- ["[1][0]" cli]
- ["[1][0]" code]
- ["[1][0]" environment]
- ["[1][0]" json]
- ["[1][0]" text]
- ["[1][0]" tree]
- ["[1][0]" type]
- ["[1][0]" xml]])
+ ["[0]" /]])
(.def .public documentation
(.List $.Module)
@@ -133,11 +124,4 @@
($.documentation /.codec
"Decode the output of a parser using a codec."
[(codec codec parser)])]
- [/cli.documentation
- /code.documentation
- /environment.documentation
- /json.documentation
- /text.documentation
- /tree.documentation
- /type.documentation
- /xml.documentation]))
+ []))
diff --git a/stdlib/source/documentation/lux/control/parser/cli.lux b/stdlib/source/documentation/lux/control/parser/cli.lux
deleted file mode 100644
index f76bb6e1a..000000000
--- a/stdlib/source/documentation/lux/control/parser/cli.lux
+++ /dev/null
@@ -1,57 +0,0 @@
-(.require
- [library
- [lux (.except parameter)
- ["$" documentation (.only documentation:)]
- [data
- [text (.only \n)
- ["%" \\format (.only format)]]]]]
- [\\library
- ["[0]" /]])
-
-(documentation: (/.Parser it)
- "A command-line interface parser.")
-
-(documentation: /.result
- "Executes the parser and verifies that all inputs are processed."
- [(result parser inputs)])
-
-(documentation: /.any
- "Just returns the next input without applying any logic.")
-
-(documentation: /.parse
- "Parses the next input with a parsing function."
- [(parse parser)])
-
-(documentation: /.this
- "Checks that a token is in the inputs."
- [(this reference)])
-
-(documentation: /.somewhere
- "Given a parser, tries to parse it somewhere in the inputs (i.e. not necessarily parsing the immediate inputs)."
- [(somewhere cli)])
-
-(documentation: /.end
- "Ensures there are no more inputs.")
-
-(documentation: /.named
- "Parses a named parameter and yields its value."
- [(named name value)])
-
-(documentation: /.parameter
- "Parses a parameter that can have either a short or a long name."
- [(parameter [short long] value)])
-
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [..Parser
- ..result
- ..any
- ..parse
- ..this
- ..somewhere
- ..end
- ..named
- ..parameter]
- []))
diff --git a/stdlib/source/documentation/lux/control/parser/code.lux b/stdlib/source/documentation/lux/control/parser/code.lux
deleted file mode 100644
index 9347075dd..000000000
--- a/stdlib/source/documentation/lux/control/parser/code.lux
+++ /dev/null
@@ -1,115 +0,0 @@
-(.require
- [library
- [lux (.except nat int rev local not symbol)
- ["$" documentation (.only documentation:)]
- [data
- [text (.only \n)
- ["%" \\format (.only format)]]]
- [meta
- [macro
- ["[0]" template]]]]]
- [\\library
- ["[0]" /]])
-
-(documentation: (/.Parser it)
- "A Lux code parser.")
-
-(documentation: /.any
- "Yields the next input without applying any logic.")
-
-(with_template [<query> <check>]
- [(`` (documentation: <query>
- (format "Parses the next " (,, (template.text [<query>])) " input.")))
- (`` (documentation: <check>
- (format "Checks for a specific " (,, (template.text [<query>])) " input.")))]
-
- [/.bit /.this_bit]
- [/.nat /.this_nat]
- [/.int /.this_int]
- [/.rev /.this_rev]
- [/.frac /.this_frac]
- [/.text /.this_text]
- [/.symbol /.this_symbol]
- )
-
-(documentation: /.this
- "Ensures the given Code is the next input."
- [(this code)])
-
-(with_template [<query> <check> <desc>]
- [(documentation: <query>
- (format "Parse a local " <desc> " (a " <desc> " that has no module prefix)."))
- (documentation: <check>
- (format "Checks for a specific local " <desc> " (a " <desc> " that has no module prefix)."))]
-
- [/.local /.this_local "local symbol"]
- )
-
-(with_template [<name>]
- [(`` (documentation: <name>
- (format "Parses the contents of a " (,, (template.text [<name>])) ".")))]
-
- [/.form]
- [/.variant]
- [/.tuple]
- )
-
-(documentation: /.end
- "Verifies there are no more inputs.")
-
-(documentation: /.end?
- "Checks whether there are no more inputs.")
-
-(documentation: /.result
- "Executes a parser against a stream of code, and verifies all the inputs are consumed."
- [(result parser inputs)])
-
-(documentation: /.locally
- "Runs parser against the given list of inputs."
- [(locally inputs parser)])
-
-(documentation: /.not
- "Yields the next Code token if the parser fails."
- [(not expected_to_fail)])
-
-(documentation: /.next
- "Yields the next Code token without consuming it from the input stream.")
-
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [..Parser
- ..any
-
- ..bit
- ..this_bit
- ..nat
- ..this_nat
- ..int
- ..this_int
- ..rev
- ..this_rev
- ..frac
- ..this_frac
- ..text
- ..this_text
- ..symbol
- ..this_symbol
-
- ..this
-
- ..local
- ..this_local
-
- ..form
- ..tuple
-
- ..variant
- ..end
- ..end?
- ..result
- ..locally
- ..not
- ..next]
- []))
diff --git a/stdlib/source/documentation/lux/control/parser/environment.lux b/stdlib/source/documentation/lux/control/parser/environment.lux
deleted file mode 100644
index 345d4aaa3..000000000
--- a/stdlib/source/documentation/lux/control/parser/environment.lux
+++ /dev/null
@@ -1,43 +0,0 @@
-(.require
- [library
- [lux (.except)
- ["$" documentation (.only documentation:)]
- [data
- [text (.only \n)
- ["%" \\format (.only format)]]]]]
- [\\library
- ["[0]" /]])
-
-(documentation: /.Property
- "A property in the environment.")
-
-(documentation: /.Environment
- "An abstraction for environment variables of a program.")
-
-(documentation: (/.Parser it)
- "A parser of environment variables of a program.")
-
-(documentation: /.empty
- "An empty environment.")
-
-(documentation: /.property
- ""
- [(property name)])
-
-(documentation: /.result
- (format "Executes a parser against the given environment variables."
- \n "Does not check whether all environment variables were parsed, since they're usually an open set.")
- [(result parser environment)])
-
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [..Property
- ..Environment
- ..Parser
- ..empty
- ..property
- ..result
- ($.default /.unknown_property)]
- []))
diff --git a/stdlib/source/documentation/lux/control/parser/type.lux b/stdlib/source/documentation/lux/control/parser/type.lux
deleted file mode 100644
index 2ecedfe39..000000000
--- a/stdlib/source/documentation/lux/control/parser/type.lux
+++ /dev/null
@@ -1,141 +0,0 @@
-(.require
- [library
- [lux (.except local function)
- ["$" documentation (.only documentation:)]
- [data
- [text (.only \n)
- ["%" \\format (.only format)]]]
- [meta
- [macro
- ["[0]" template]]]]]
- [\\library
- ["[0]" /]])
-
-(documentation: /.Env
- "An environment for type parsing.")
-
-(documentation: (/.Parser it)
- "A parser of Lux types.")
-
-(documentation: /.fresh
- "An empty parsing environment.")
-
-(documentation: /.result
- (format "Applies a parser against a type."
- \n "Verifies that the parser fully consumes the type's information.")
- [(result poly type)])
-
-(documentation: /.env
- "Yields the current parsing environment.")
-
-(documentation: /.next
- "Inspect a type in the input stream without consuming it.")
-
-(documentation: /.any
- "Yields a type, without examination.")
-
-(documentation: /.local
- "Apply a parser to the given inputs."
- [(local types poly)])
-
-(documentation: /.with_extension
- ""
- [(with_extension type poly)])
-
-(with_template [<name>]
- [(`` (documentation: <name>
- (format "Parses the contents of a " (,, (template.text [<name>])) " type.")))]
-
- [/.variant]
- [/.tuple]
- )
-
-(documentation: /.polymorphic
- ""
- [(polymorphic poly)])
-
-(documentation: /.function
- "Parses a function's inputs and output."
- [(function in_poly out_poly)])
-
-(documentation: /.applied
- "Parses a type application."
- [(applied poly)])
-
-(with_template [<name> <doc>]
- [(documentation: <name>
- <doc>)]
-
- [/.exactly "Parses a type exactly."]
- [/.sub "Parses a sub type."]
- [/.super "Parses a super type."]
- )
-
-(documentation: /.argument
- ""
- [(argument env idx)])
-
-(documentation: /.this_parameter
- ""
- [(this_parameter id)])
-
-(documentation: /.existential
- "Yields an existential type.")
-
-(documentation: /.named
- "Yields a named type.")
-
-(documentation: /.recursive
- ""
- [(recursive poly)])
-
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- (format "Parsing of Lux types."
- \n "Used mostly for polytypic programming.")
- [..Env
- ..Parser
- ..fresh
- ..result
- ..env
- ..next
- ..any
- ..local
- ..with_extension
-
- ..variant
- ..tuple
-
- ..polymorphic
- ..function
- ..applied
-
- ..exactly
- ..sub
- ..super
-
- ..argument
- ..this_parameter
- ..existential
- ..named
- ..recursive
-
- ($.default /.not_existential)
- ($.default /.not_recursive)
- ($.default /.not_named)
- ($.default /.not_parameter)
- ($.default /.unknown_parameter)
- ($.default /.not_function)
- ($.default /.not_application)
- ($.default /.not_polymorphic)
- ($.default /.not_variant)
- ($.default /.not_tuple)
- ($.default /.types_do_not_match)
- ($.default /.wrong_parameter)
- ($.default /.empty_input)
- ($.default /.unconsumed_input)
- ($.default /.parameter)
- ($.default /.recursive_self)
- ($.default /.recursive_call)]
- []))
diff --git a/stdlib/source/documentation/lux/meta.lux b/stdlib/source/documentation/lux/meta.lux
index 71dc925dd..3e6cdd38e 100644
--- a/stdlib/source/documentation/lux/meta.lux
+++ b/stdlib/source/documentation/lux/meta.lux
@@ -1,10 +1,12 @@
(.require
[library
- [lux (.except macro)
+ [lux (.except)
["$" documentation]
[data
["[0]" text (.only \n)
- ["%" \\format (.only format)]]]]]
+ ["%" \\format (.only format)]]
+ [collection
+ ["[0]" list]]]]]
[\\library
["[0]" /]]
["[0]" /
@@ -13,7 +15,25 @@
["[1][0]" symbol]
["[1][0]" type]
["[1][0]" macro]
- ["[1][0]" target]])
+ ["[1][0]" target]
+ ["[1][0]/" compiler
+ ["[1][0]" phase]
+ [language
+ [lux
+ ["[1][0]" analysis]
+ ["[1][0]" declaration]
+ ["[1][0]" generation]
+ ["[1][0]" synthesis]]]]])
+
+(.def /compiler
+ (.List $.Module)
+ (list.together
+ (list /compiler/phase.documentation
+ /compiler/analysis.documentation
+ /compiler/declaration.documentation
+ /compiler/generation.documentation
+ /compiler/synthesis.documentation
+ )))
(.def .public documentation
(.List $.Module)
@@ -169,4 +189,5 @@
/symbol.documentation
/type.documentation
/macro.documentation
- /target.documentation]))
+ /target.documentation
+ ../compiler]))
diff --git a/stdlib/source/documentation/lux/meta/code.lux b/stdlib/source/documentation/lux/meta/code.lux
index df50d5049..d1bf31f01 100644
--- a/stdlib/source/documentation/lux/meta/code.lux
+++ b/stdlib/source/documentation/lux/meta/code.lux
@@ -1,15 +1,88 @@
(.require
[library
- [lux (.except char local global)
+ [lux (.except)
["$" documentation]
[data
- [text
+ [text (.only \n)
["%" \\format (.only format)]]
[collection
- ["[0]" list]]]]]
+ ["[0]" list]]]
+ [meta
+ [macro
+ ["[0]" template]]]]]
+ ["[0]" \\parser]
[\\library
["[0]" /]])
+(`` (.def \\parser
+ (.List $.Module)
+ ($.module \\parser._
+ ""
+ [($.documentation (\\parser.Parser it)
+ "A Lux code parser.")
+
+ ($.documentation \\parser.any
+ "Yields the next input without applying any logic.")
+
+ (,, (with_template [<query> <check>]
+ [(`` ($.documentation <query>
+ (format "Parses the next " (,, (template.text [<query>])) " input.")))
+ (`` ($.documentation <check>
+ (format "Checks for a specific " (,, (template.text [<query>])) " input.")))]
+
+ [\\parser.bit \\parser.this_bit]
+ [\\parser.nat \\parser.this_nat]
+ [\\parser.int \\parser.this_int]
+ [\\parser.rev \\parser.this_rev]
+ [\\parser.frac \\parser.this_frac]
+ [\\parser.text \\parser.this_text]
+ [\\parser.symbol \\parser.this_symbol]
+ ))
+
+ ($.documentation \\parser.this
+ "Ensures the given Code is the next input."
+ [(this code)])
+
+ (,, (with_template [<query> <check> <desc>]
+ [($.documentation <query>
+ (format "Parse a local " <desc> " (a " <desc> " that has no module prefix)."))
+ ($.documentation <check>
+ (format "Checks for a specific local " <desc> " (a " <desc> " that has no module prefix)."))]
+
+ [\\parser.local \\parser.this_local "local symbol"]
+ ))
+
+ (,, (with_template [<name>]
+ [(`` ($.documentation <name>
+ (format "Parses the contents of a " (,, (template.text [<name>])) ".")))]
+
+ [\\parser.form]
+ [\\parser.variant]
+ [\\parser.tuple]
+ ))
+
+ ($.documentation \\parser.end
+ "Verifies there are no more inputs.")
+
+ ($.documentation \\parser.end?
+ "Checks whether there are no more inputs.")
+
+ ($.documentation \\parser.result
+ "Executes a parser against a stream of code, and verifies all the inputs are consumed."
+ [(result parser inputs)])
+
+ ($.documentation \\parser.locally
+ "Runs parser against the given list of inputs."
+ [(locally inputs parser)])
+
+ ($.documentation \\parser.not
+ "Yields the next Code token if the parser fails."
+ [(not expected_to_fail)])
+
+ ($.documentation \\parser.next
+ "Yields the next Code token without consuming it from the input stream.")]
+ [])))
+
(.def .public documentation
(.List $.Module)
($.module /._
@@ -34,4 +107,4 @@
($.documentation /.replaced
""
[(replaced original substitute ast)])]
- []))
+ [..\\parser]))
diff --git a/stdlib/source/documentation/lux/tool/compiler/language/lux/analysis.lux b/stdlib/source/documentation/lux/meta/compiler/language/lux/analysis.lux
index 7daade0e8..7daade0e8 100644
--- a/stdlib/source/documentation/lux/tool/compiler/language/lux/analysis.lux
+++ b/stdlib/source/documentation/lux/meta/compiler/language/lux/analysis.lux
diff --git a/stdlib/source/documentation/lux/tool/compiler/language/lux/declaration.lux b/stdlib/source/documentation/lux/meta/compiler/language/lux/declaration.lux
index cc2088576..cc2088576 100644
--- a/stdlib/source/documentation/lux/tool/compiler/language/lux/declaration.lux
+++ b/stdlib/source/documentation/lux/meta/compiler/language/lux/declaration.lux
diff --git a/stdlib/source/documentation/lux/tool/compiler/language/lux/generation.lux b/stdlib/source/documentation/lux/meta/compiler/language/lux/generation.lux
index 295ada218..295ada218 100644
--- a/stdlib/source/documentation/lux/tool/compiler/language/lux/generation.lux
+++ b/stdlib/source/documentation/lux/meta/compiler/language/lux/generation.lux
diff --git a/stdlib/source/documentation/lux/tool/compiler/language/lux/synthesis.lux b/stdlib/source/documentation/lux/meta/compiler/language/lux/synthesis.lux
index dcfe3ce0a..dcfe3ce0a 100644
--- a/stdlib/source/documentation/lux/tool/compiler/language/lux/synthesis.lux
+++ b/stdlib/source/documentation/lux/meta/compiler/language/lux/synthesis.lux
diff --git a/stdlib/source/documentation/lux/tool/compiler/phase.lux b/stdlib/source/documentation/lux/meta/compiler/phase.lux
index 5efcf5d0f..5efcf5d0f 100644
--- a/stdlib/source/documentation/lux/tool/compiler/phase.lux
+++ b/stdlib/source/documentation/lux/meta/compiler/phase.lux
diff --git a/stdlib/source/documentation/lux/meta/type.lux b/stdlib/source/documentation/lux/meta/type.lux
index 541e3978c..f2335eb24 100644
--- a/stdlib/source/documentation/lux/meta/type.lux
+++ b/stdlib/source/documentation/lux/meta/type.lux
@@ -1,10 +1,14 @@
(.require
[library
- [lux (.except function as let)
+ [lux (.except)
["$" documentation]
[data
["[0]" text (.only \n)
- ["%" \\format]]]]]
+ ["%" \\format (.only format)]]]
+ [meta
+ [macro
+ ["[0]" template]]]]]
+ ["[0]" \\parser]
[\\library
["[0]" /]]
["[0]" /
@@ -19,6 +23,108 @@
["[1][0]" unit]
["[1][0]" variance]])
+(`` (.def \\parser
+ (.List $.Module)
+ ($.module \\parser._
+ (format "Parsing of Lux types."
+ \n "Used mostly for polytypic programming.")
+ [($.default \\parser.not_existential)
+ ($.default \\parser.not_recursive)
+ ($.default \\parser.not_named)
+ ($.default \\parser.not_parameter)
+ ($.default \\parser.unknown_parameter)
+ ($.default \\parser.not_function)
+ ($.default \\parser.not_application)
+ ($.default \\parser.not_polymorphic)
+ ($.default \\parser.not_variant)
+ ($.default \\parser.not_tuple)
+ ($.default \\parser.types_do_not_match)
+ ($.default \\parser.wrong_parameter)
+ ($.default \\parser.empty_input)
+ ($.default \\parser.unconsumed_input)
+ ($.default \\parser.parameter)
+ ($.default \\parser.recursive_self)
+ ($.default \\parser.recursive_call)
+
+ ($.documentation \\parser.Env
+ "An environment for type parsing.")
+
+ ($.documentation (\\parser.Parser it)
+ "A parser of Lux types.")
+
+ ($.documentation \\parser.fresh
+ "An empty parsing environment.")
+
+ ($.documentation \\parser.result
+ (format "Applies a parser against a type."
+ \n "Verifies that the parser fully consumes the type's information.")
+ [(result poly type)])
+
+ ($.documentation \\parser.env
+ "Yields the current parsing environment.")
+
+ ($.documentation \\parser.next
+ "Inspect a type in the input stream without consuming it.")
+
+ ($.documentation \\parser.any
+ "Yields a type, without examination.")
+
+ ($.documentation \\parser.local
+ "Apply a parser to the given inputs."
+ [(local types poly)])
+
+ ($.documentation \\parser.with_extension
+ ""
+ [(with_extension type poly)])
+
+ (,, (with_template [<name>]
+ [(`` ($.documentation <name>
+ (format "Parses the contents of a " (,, (template.text [<name>])) " type.")))]
+
+ [\\parser.variant]
+ [\\parser.tuple]
+ ))
+
+ ($.documentation \\parser.polymorphic
+ ""
+ [(polymorphic poly)])
+
+ ($.documentation \\parser.function
+ "Parses a function's inputs and output."
+ [(function in_poly out_poly)])
+
+ ($.documentation \\parser.applied
+ "Parses a type application."
+ [(applied poly)])
+
+ (,, (with_template [<name> <doc>]
+ [($.documentation <name>
+ <doc>)]
+
+ [\\parser.exactly "Parses a type exactly."]
+ [\\parser.sub "Parses a sub type."]
+ [\\parser.super "Parses a super type."]
+ ))
+
+ ($.documentation \\parser.argument
+ ""
+ [(argument env idx)])
+
+ ($.documentation \\parser.this_parameter
+ ""
+ [(this_parameter id)])
+
+ ($.documentation \\parser.existential
+ "Yields an existential type.")
+
+ ($.documentation \\parser.named
+ "Yields a named type.")
+
+ ($.documentation \\parser.recursive
+ ""
+ [(recursive poly)])]
+ [])))
+
(`` (.def .public documentation
(.List $.Module)
($.module /._
@@ -153,7 +259,9 @@
"Local bindings for types."
[(let [side (Either Int Frac)]
(List [side side]))])]
- [/primitive.documentation
+ [..\\parser
+
+ /primitive.documentation
/check.documentation
/dynamic.documentation
/implicit.documentation
diff --git a/stdlib/source/documentation/lux/program.lux b/stdlib/source/documentation/lux/program.lux
index 87e9b607a..4617fafa1 100644
--- a/stdlib/source/documentation/lux/program.lux
+++ b/stdlib/source/documentation/lux/program.lux
@@ -7,9 +7,48 @@
[data
["[0]" text (.only \n)
["%" \\format (.only format)]]]]]
+ ["[0]" \\parser]
[\\library
["[0]" /]])
+(.def \\parser
+ (.List $.Module)
+ ($.module \\parser._
+ ""
+ [($.documentation (\\parser.Parser it)
+ "A command-line interface parser.")
+
+ ($.documentation \\parser.result
+ "Executes the parser and verifies that all inputs are processed."
+ [(result parser inputs)])
+
+ ($.documentation \\parser.any
+ "Just returns the next input without applying any logic.")
+
+ ($.documentation \\parser.parse
+ "Parses the next input with a parsing function."
+ [(parse parser)])
+
+ ($.documentation \\parser.this
+ "Checks that a token is in the inputs."
+ [(this reference)])
+
+ ($.documentation \\parser.somewhere
+ "Given a parser, tries to parse it somewhere in the inputs (i.e. not necessarily parsing the immediate inputs)."
+ [(somewhere cli)])
+
+ ($.documentation \\parser.end
+ "Ensures there are no more inputs.")
+
+ ($.documentation \\parser.named
+ "Parses a named parameter and yields its value."
+ [(named name value)])
+
+ ($.documentation \\parser.parameter
+ "Parses a parameter that can have either a short or a long name."
+ [(parameter [short long] value)])]
+ []))
+
(.def .public documentation
(.List $.Module)
($.module /._
@@ -26,4 +65,4 @@
(do io.monad
[data (initialize program with config)]
(do_something_with data)))])]
- []))
+ [..\\parser]))
diff --git a/stdlib/source/documentation/lux/tool.lux b/stdlib/source/documentation/lux/tool.lux
index 0c67d1842..c5d46aba3 100644
--- a/stdlib/source/documentation/lux/tool.lux
+++ b/stdlib/source/documentation/lux/tool.lux
@@ -8,21 +8,6 @@
[collection
["[0]" list]]]]]
["[0]" /
- [compiler
- ["[1][0]" phase]
- [language
- [lux
- ["[1][0]" analysis]
- ["[1][0]" declaration]
- ["[1][0]" generation]
- ["[1][0]" synthesis]]]]])
+ ])
+
-(.def .public documentation
- (.List $.Module)
- (list.together
- (list /phase.documentation
- /analysis.documentation
- /declaration.documentation
- /generation.documentation
- /synthesis.documentation
- )))
diff --git a/stdlib/source/documentation/lux/world/environment.lux b/stdlib/source/documentation/lux/world/environment.lux
index 6f842b4b9..4703069ed 100644
--- a/stdlib/source/documentation/lux/world/environment.lux
+++ b/stdlib/source/documentation/lux/world/environment.lux
@@ -5,9 +5,38 @@
[data
["[0]" text (.only \n)
["%" \\format (.only format)]]]]]
+ ["[0]" \\parser]
[\\library
["[0]" /]])
+(.def \\parser
+ (.List $.Module)
+ ($.module \\parser._
+ ""
+ [($.default \\parser.unknown_property)
+
+ ($.documentation \\parser.Property
+ "A property in the environment.")
+
+ ($.documentation \\parser.Environment
+ "An abstraction for environment variables of a program.")
+
+ ($.documentation (\\parser.Parser it)
+ "A parser of environment variables of a program.")
+
+ ($.documentation \\parser.empty
+ "An empty environment.")
+
+ ($.documentation \\parser.property
+ ""
+ [(property name)])
+
+ ($.documentation \\parser.result
+ (format "Executes a parser against the given environment variables."
+ \n "Does not check whether all environment variables were parsed, since they're usually an open set.")
+ [(result parser environment)])]
+ []))
+
(.def .public documentation
(.List $.Module)
($.module /._
@@ -26,4 +55,4 @@
($.documentation /.mock
""
[(mock environment home directory)])]
- []))
+ [..\\parser]))