aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/documentation
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/documentation')
-rw-r--r--stdlib/source/documentation/lux/meta.lux317
-rw-r--r--stdlib/source/documentation/lux/meta/code.lux192
-rw-r--r--stdlib/source/documentation/lux/meta/compiler/language/lux/analysis.lux172
-rw-r--r--stdlib/source/documentation/lux/meta/compiler/language/lux/declaration.lux49
-rw-r--r--stdlib/source/documentation/lux/meta/compiler/language/lux/generation.lux103
-rw-r--r--stdlib/source/documentation/lux/meta/compiler/language/lux/synthesis.lux257
-rw-r--r--stdlib/source/documentation/lux/meta/compiler/phase.lux43
-rw-r--r--stdlib/source/documentation/lux/meta/extension.lux47
-rw-r--r--stdlib/source/documentation/lux/meta/location.lux31
-rw-r--r--stdlib/source/documentation/lux/meta/macro.lux158
-rw-r--r--stdlib/source/documentation/lux/meta/macro/local.lux31
-rw-r--r--stdlib/source/documentation/lux/meta/macro/syntax.lux65
-rw-r--r--stdlib/source/documentation/lux/meta/macro/syntax/check.lux23
-rw-r--r--stdlib/source/documentation/lux/meta/macro/syntax/declaration.lux31
-rw-r--r--stdlib/source/documentation/lux/meta/macro/syntax/definition.lux35
-rw-r--r--stdlib/source/documentation/lux/meta/macro/syntax/export.lux21
-rw-r--r--stdlib/source/documentation/lux/meta/macro/syntax/input.lux25
-rw-r--r--stdlib/source/documentation/lux/meta/macro/syntax/type/variable.lux25
-rw-r--r--stdlib/source/documentation/lux/meta/macro/template.lux97
-rw-r--r--stdlib/source/documentation/lux/meta/static.lux81
-rw-r--r--stdlib/source/documentation/lux/meta/symbol.lux27
-rw-r--r--stdlib/source/documentation/lux/meta/target.lux53
-rw-r--r--stdlib/source/documentation/lux/meta/target/js.lux171
-rw-r--r--stdlib/source/documentation/lux/meta/target/jvm/type.lux95
-rw-r--r--stdlib/source/documentation/lux/meta/target/jvm/type/alias.lux19
-rw-r--r--stdlib/source/documentation/lux/meta/target/jvm/type/box.lux29
-rw-r--r--stdlib/source/documentation/lux/meta/target/jvm/type/category.lux39
-rw-r--r--stdlib/source/documentation/lux/meta/target/jvm/type/descriptor.lux63
-rw-r--r--stdlib/source/documentation/lux/meta/target/jvm/type/lux.lux35
-rw-r--r--stdlib/source/documentation/lux/meta/target/jvm/type/parser.lux85
-rw-r--r--stdlib/source/documentation/lux/meta/target/jvm/type/reflection.lux53
-rw-r--r--stdlib/source/documentation/lux/meta/target/jvm/type/signature.lux75
-rw-r--r--stdlib/source/documentation/lux/meta/target/lua.lux161
-rw-r--r--stdlib/source/documentation/lux/meta/target/python.lux201
-rw-r--r--stdlib/source/documentation/lux/meta/target/ruby.lux203
-rw-r--r--stdlib/source/documentation/lux/meta/type.lux506
-rw-r--r--stdlib/source/documentation/lux/meta/type/check.lux137
-rw-r--r--stdlib/source/documentation/lux/meta/type/dynamic.lux37
-rw-r--r--stdlib/source/documentation/lux/meta/type/implicit.lux81
-rw-r--r--stdlib/source/documentation/lux/meta/type/poly.lux21
-rw-r--r--stdlib/source/documentation/lux/meta/type/primitive.lux217
-rw-r--r--stdlib/source/documentation/lux/meta/type/quotient.lux67
-rw-r--r--stdlib/source/documentation/lux/meta/type/refinement.lux85
-rw-r--r--stdlib/source/documentation/lux/meta/type/resource.lux175
-rw-r--r--stdlib/source/documentation/lux/meta/type/unit.lux127
-rw-r--r--stdlib/source/documentation/lux/meta/type/variance.lux25
46 files changed, 2336 insertions, 2254 deletions
diff --git a/stdlib/source/documentation/lux/meta.lux b/stdlib/source/documentation/lux/meta.lux
index 42e917dd5..df0c93de6 100644
--- a/stdlib/source/documentation/lux/meta.lux
+++ b/stdlib/source/documentation/lux/meta.lux
@@ -6,7 +6,7 @@
["[0]" text (.only \n)
["%" \\format (.only format)]]
[collection
- ["[0]" list]]]]]
+ ["[0]" list (.use "[1]#[0]" monoid)]]]]]
[\\library
["[0]" /]]
["[0]" /
@@ -27,8 +27,8 @@
["[1][0]" generation]
["[1][0]" synthesis]]]]])
-(.def /compiler
- (.List $.Module)
+(def /compiler
+ (List $.Documentation)
(list.together
(list /compiler/phase.documentation
/compiler/analysis.documentation
@@ -37,161 +37,166 @@
/compiler/synthesis.documentation
)))
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- "Functions for extracting information from the state of the compiler."
- [($.definition /.functor)
- ($.definition /.apply)
- ($.definition /.monad)
- ($.definition /.lifted)
- ($.definition /.try)
+(def .public documentation
+ (List $.Documentation)
+ (list.partial ($.module /._
+ "Functions for extracting information from the state of the compiler.")
- ($.definition /.result'
- (format "Evaluates a computation that depends on Lux's compiler state."
- \n "Also returns a (potentially modified) compiler state.")
- [(result' lux action)])
-
- ($.definition /.result
- "Evaluates a computation that depends on Lux's compiler state."
- [(result lux action)])
-
- ($.definition /.either
- "Pick whichever computation succeeds."
- [(either left right)])
-
- ($.definition /.assertion
- "Fails with the given message if the test is #0."
- [(assertion message test)])
-
- ($.definition /.failure
- "Fails with the given error message."
- [(failure error)])
-
- ($.definition /.module
- "Looks-up a module with the given name."
- [(module name)])
-
- ($.definition /.current_module_name
- "The name of the module currently being compiled, if any.")
+ ($.definition /.functor)
+ ($.definition /.apply)
+ ($.definition /.monad)
+ ($.definition /.lifted)
+ ($.definition /.try)
- ($.definition /.current_module
- "The module currently being compiled, if any.")
+ ($.definition /.result'
+ (format "Evaluates a computation that depends on Lux's compiler state."
+ \n "Also returns a (potentially modified) compiler state.")
+ [(result' lux action)])
- ($.definition /.normal
- (format "If given a name without a module prefix, gives it the current module's name as prefix."
- \n "Otherwise, returns the name as-is.")
- [(normal name)])
+ ($.definition /.result
+ "Evaluates a computation that depends on Lux's compiler state."
+ [(result lux action)])
- ($.definition /.macro
- "Looks-up a macro known by the given name."
- [(macro full_name)])
+ ($.definition /.either
+ "Pick whichever computation succeeds."
+ [(either left right)])
- ($.definition /.seed
- (format "The current value of a number tracked by the compiler."
- \n "Also increases the value, so it's different next time it is seen."
- \n "This number can be used for generating data 'randomly' during compilation."))
-
- ($.definition /.module_exists?
- ""
- [(module_exists? module)])
-
- ($.definition /.var_type
- "Looks-up the type of a local variable somewhere in the environment."
- [(var_type name)])
-
- ($.definition /.definition
- "Looks-up a definition's whole data in the available modules (including the current one)."
- [(definition name)])
-
- ($.definition /.export
- (format "Looks-up a definition in the available modules (including the current one)."
- \n "The look-up only succeeds if the definition has been exported.")
- [(export name)])
-
- ($.definition /.definition_type
- "Looks-up a definition's type in the available modules (including the current one)."
- [(definition_type name)])
-
- ($.definition /.type
- "Looks-up the type of either a local variable or a definition."
- [(type name)])
-
- ($.definition /.type_definition
- "Finds the value of a type definition (such as Int, Any or Lux)."
- [(type_definition name)])
-
- ($.definition /.globals
- "The entire list of globals in a module (including the non-exported/private ones)."
- [(globals module)])
-
- ($.definition /.definitions
- "The entire list of definitions in a module (including the non-exported/private ones)."
- [(definitions module)])
-
- ($.definition /.exports
- "All the exported definitions in a module."
- [(exports module_name)])
-
- ($.definition /.modules
- "All the available modules (including the current one).")
-
- ($.definition /.tags_of
- "All the tags associated with a type definition."
- [(tags_of type_name)])
-
- ($.definition /.location
- "The location of the current expression being analyzed.")
-
- ($.definition /.expected_type
- "The expected type of the current expression being analyzed.")
-
- ($.definition /.imported_modules
- "All the modules imported by a specified module."
- [(imported_modules module_name)])
-
- ($.definition /.imported_by?
- ""
- [(imported_by? import module)])
-
- ($.definition /.imported?
- "Checks if the given module has been imported by the current module."
- [(imported? import)])
-
- ($.definition /.tag
- "Given a tag, finds out what is its index, its related tag-list and its associated type."
- [(tag tag_name)])
-
- ($.definition /.slot
- "Given a slot, finds out what is its index, its related slot-list and its associated type."
- [(slot slot_name)])
-
- ($.definition /.tag_lists
- "All the tag-lists defined in a module, with their associated types."
- [(tag_lists module)])
-
- ($.definition /.locals
- "All the local variables currently in scope, separated in different scopes.")
-
- ($.definition /.de_aliased
- "Given an aliased definition's name, returns the original definition being referenced."
- [(de_aliased def_name)])
-
- ($.definition /.compiler_state
- "Obtains the current state of the compiler.")
-
- ($.definition /.type_context
- "The current type-checking context.")
-
- ($.definition /.eval
- ""
- [(eval type code)])]
- [/code.documentation
- /location.documentation
- /symbol.documentation
- /type.documentation
- /macro.documentation
- /static.documentation
- /extension.documentation
- /target.documentation
- ../compiler]))
+ ($.definition /.assertion
+ "Fails with the given message if the test is #0."
+ [(assertion message test)])
+
+ ($.definition /.failure
+ "Fails with the given error message."
+ [(failure error)])
+
+ ($.definition /.module
+ "Looks-up a module with the given name."
+ [(module name)])
+
+ ($.definition /.current_module_name
+ "The name of the module currently being compiled, if any.")
+
+ ($.definition /.current_module
+ "The module currently being compiled, if any.")
+
+ ($.definition /.normal
+ (format "If given a name without a module prefix, gives it the current module's name as prefix."
+ \n "Otherwise, returns the name as-is.")
+ [(normal name)])
+
+ ($.definition /.macro
+ "Looks-up a macro known by the given name."
+ [(macro full_name)])
+
+ ($.definition /.seed
+ (format "The current value of a number tracked by the compiler."
+ \n "Also increases the value, so it's different next time it is seen."
+ \n "This number can be used for generating data 'randomly' during compilation."))
+
+ ($.definition /.module_exists?
+ ""
+ [(module_exists? module)])
+
+ ($.definition /.var_type
+ "Looks-up the type of a local variable somewhere in the environment."
+ [(var_type name)])
+
+ ($.definition /.definition
+ "Looks-up a definition's whole data in the available modules (including the current one)."
+ [(definition name)])
+
+ ($.definition /.export
+ (format "Looks-up a definition in the available modules (including the current one)."
+ \n "The look-up only succeeds if the definition has been exported.")
+ [(export name)])
+
+ ($.definition /.definition_type
+ "Looks-up a definition's type in the available modules (including the current one)."
+ [(definition_type name)])
+
+ ($.definition /.type
+ "Looks-up the type of either a local variable or a definition."
+ [(type name)])
+
+ ($.definition /.type_definition
+ "Finds the value of a type definition (such as Int, Any or Lux)."
+ [(type_definition name)])
+
+ ($.definition /.globals
+ "The entire list of globals in a module (including the non-exported/private ones)."
+ [(globals module)])
+
+ ($.definition /.definitions
+ "The entire list of definitions in a module (including the non-exported/private ones)."
+ [(definitions module)])
+
+ ($.definition /.exports
+ "All the exported definitions in a module."
+ [(exports module_name)])
+
+ ($.definition /.modules
+ "All the available modules (including the current one).")
+
+ ($.definition /.tags_of
+ "All the tags associated with a type definition."
+ [(tags_of type_name)])
+
+ ($.definition /.location
+ "The location of the current expression being analyzed.")
+
+ ($.definition /.expected_type
+ "The expected type of the current expression being analyzed.")
+
+ ($.definition /.imported_modules
+ "All the modules imported by a specified module."
+ [(imported_modules module_name)])
+
+ ($.definition /.imported_by?
+ ""
+ [(imported_by? import module)])
+
+ ($.definition /.imported?
+ "Checks if the given module has been imported by the current module."
+ [(imported? import)])
+
+ ($.definition /.tag
+ "Given a tag, finds out what is its index, its related tag-list and its associated type."
+ [(tag tag_name)])
+
+ ($.definition /.slot
+ "Given a slot, finds out what is its index, its related slot-list and its associated type."
+ [(slot slot_name)])
+
+ ($.definition /.tag_lists
+ "All the tag-lists defined in a module, with their associated types."
+ [(tag_lists module)])
+
+ ($.definition /.locals
+ "All the local variables currently in scope, separated in different scopes.")
+
+ ($.definition /.de_aliased
+ "Given an aliased definition's name, returns the original definition being referenced."
+ [(de_aliased def_name)])
+
+ ($.definition /.compiler_state
+ "Obtains the current state of the compiler.")
+
+ ($.definition /.type_context
+ "The current type-checking context.")
+
+ ($.definition /.eval
+ ""
+ [(eval type code)])
+
+ (all list#composite
+ /code.documentation
+ /location.documentation
+ /symbol.documentation
+ /type.documentation
+ /macro.documentation
+ /static.documentation
+ /extension.documentation
+ /target.documentation
+ ../compiler
+ )
+ ))
diff --git a/stdlib/source/documentation/lux/meta/code.lux b/stdlib/source/documentation/lux/meta/code.lux
index ebba6189a..65e083e02 100644
--- a/stdlib/source/documentation/lux/meta/code.lux
+++ b/stdlib/source/documentation/lux/meta/code.lux
@@ -14,97 +14,101 @@
[\\library
["[0]" /]])
-(`` (.def \\parser
- (.List $.Module)
- ($.module \\parser._
- ""
- [($.definition (\\parser.Parser it)
- "A Lux code parser.")
-
- ($.definition \\parser.any
- "Yields the next input without applying any logic.")
-
- (,, (with_template [<query> <check>]
- [(`` ($.definition <query>
- (format "Parses the next " (,, (template.text [<query>])) " input.")))
- (`` ($.definition <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]
- ))
-
- ($.definition \\parser.this
- "Ensures the given Code is the next input."
- [(this code)])
-
- (,, (with_template [<query> <check> <desc>]
- [($.definition <query>
- (format "Parse a local " <desc> " (a " <desc> " that has no module prefix)."))
- ($.definition <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>]
- [(`` ($.definition <name>
- (format "Parses the contents of a " (,, (template.text [<name>])) ".")))]
-
- [\\parser.form]
- [\\parser.variant]
- [\\parser.tuple]
- ))
-
- ($.definition \\parser.end
- "Verifies there are no more inputs.")
-
- ($.definition \\parser.end?
- "Checks whether there are no more inputs.")
-
- ($.definition \\parser.result
- "Executes a parser against a stream of code, and verifies all the inputs are consumed."
- [(result parser inputs)])
-
- ($.definition \\parser.locally
- "Runs parser against the given list of inputs."
- [(locally inputs parser)])
-
- ($.definition \\parser.not
- "Yields the next Code token if the parser fails."
- [(not expected_to_fail)])
-
- ($.definition \\parser.next
- "Yields the next Code token without consuming it from the input stream.")]
- [])))
-
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.bit)
- ($.definition /.nat)
- ($.definition /.int)
- ($.definition /.rev)
- ($.definition /.frac)
- ($.definition /.text)
- ($.definition /.symbol)
- ($.definition /.form)
- ($.definition /.variant)
- ($.definition /.tuple)
-
- ($.definition /.equivalence)
- ($.definition /.format)
-
- ($.definition /.local
- "Produces a local symbol (an symbol with no module prefix).")
-
- ($.definition /.replaced
- ""
- [(replaced original substitute ast)])]
- [..\\parser]))
+(`` (def \\parser
+ (List $.Documentation)
+ (list ($.module \\parser._
+ "")
+
+ ($.definition (\\parser.Parser it)
+ "A Lux code parser.")
+
+ ($.definition \\parser.any
+ "Yields the next input without applying any logic.")
+
+ (,, (with_template [<query> <check>]
+ [(`` ($.definition <query>
+ (format "Parses the next " (,, (template.text [<query>])) " input.")))
+ (`` ($.definition <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]
+ ))
+
+ ($.definition \\parser.this
+ "Ensures the given Code is the next input."
+ [(this code)])
+
+ (,, (with_template [<query> <check> <desc>]
+ [($.definition <query>
+ (format "Parse a local " <desc> " (a " <desc> " that has no module prefix)."))
+ ($.definition <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>]
+ [(`` ($.definition <name>
+ (format "Parses the contents of a " (,, (template.text [<name>])) ".")))]
+
+ [\\parser.form]
+ [\\parser.variant]
+ [\\parser.tuple]
+ ))
+
+ ($.definition \\parser.end
+ "Verifies there are no more inputs.")
+
+ ($.definition \\parser.end?
+ "Checks whether there are no more inputs.")
+
+ ($.definition \\parser.result
+ "Executes a parser against a stream of code, and verifies all the inputs are consumed."
+ [(result parser inputs)])
+
+ ($.definition \\parser.locally
+ "Runs parser against the given list of inputs."
+ [(locally inputs parser)])
+
+ ($.definition \\parser.not
+ "Yields the next Code token if the parser fails."
+ [(not expected_to_fail)])
+
+ ($.definition \\parser.next
+ "Yields the next Code token without consuming it from the input stream.")
+ )))
+
+(def .public documentation
+ (List $.Documentation)
+ (list.partial ($.module /._
+ "")
+
+ ($.definition /.bit)
+ ($.definition /.nat)
+ ($.definition /.int)
+ ($.definition /.rev)
+ ($.definition /.frac)
+ ($.definition /.text)
+ ($.definition /.symbol)
+ ($.definition /.form)
+ ($.definition /.variant)
+ ($.definition /.tuple)
+
+ ($.definition /.equivalence)
+ ($.definition /.format)
+
+ ($.definition /.local
+ "Produces a local symbol (an symbol with no module prefix).")
+
+ ($.definition /.replaced
+ ""
+ [(replaced original substitute ast)])
+
+ ..\\parser
+ ))
diff --git a/stdlib/source/documentation/lux/meta/compiler/language/lux/analysis.lux b/stdlib/source/documentation/lux/meta/compiler/language/lux/analysis.lux
index 5069f761c..45d71946e 100644
--- a/stdlib/source/documentation/lux/meta/compiler/language/lux/analysis.lux
+++ b/stdlib/source/documentation/lux/meta/compiler/language/lux/analysis.lux
@@ -14,96 +14,100 @@
[\\library
["[0]" /]])
-(`` (.def \\parser
- (.List $.Module)
- ($.module \\parser._
- ""
- [($.definition \\parser.cannot_parse)
- ($.definition \\parser.unconsumed_input)
+(`` (def \\parser
+ (List $.Documentation)
+ (list ($.module \\parser._
+ "")
- ($.definition (\\parser.Parser it)
- "A parser for Lux code analysis nodes.")
+ ($.definition \\parser.cannot_parse)
+ ($.definition \\parser.unconsumed_input)
- ($.definition \\parser.result
- "Executes a parser and makes sure no inputs go unconsumed."
- [(result parser input)])
+ ($.definition (\\parser.Parser it)
+ "A parser for Lux code analysis nodes.")
- ($.definition \\parser.any
- "Matches any value, without discrimination.")
+ ($.definition \\parser.result
+ "Executes a parser and makes sure no inputs go unconsumed."
+ [(result parser input)])
- ($.definition \\parser.end
- "Ensures there are no more inputs.")
+ ($.definition \\parser.any
+ "Matches any value, without discrimination.")
- ($.definition \\parser.end?
- "Checks whether there are no more inputs.")
+ ($.definition \\parser.end
+ "Ensures there are no more inputs.")
- (,, (with_template [<query> <assertion>]
- [($.definition <query>
- (format "Queries for a " (template.text [<query>]) " value."))
- ($.definition <assertion>
- (format "Assert a specific " (template.text [<query>]) " value."))]
+ ($.definition \\parser.end?
+ "Checks whether there are no more inputs.")
- [\\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.local \\parser.this_local]
- [\\parser.foreign \\parser.this_foreign]
- [\\parser.constant \\parser.this_constant]
- ))
+ (,, (with_template [<query> <assertion>]
+ [($.definition <query>
+ (format "Queries for a " (template.text [<query>]) " value."))
+ ($.definition <assertion>
+ (format "Assert a specific " (template.text [<query>]) " value."))]
- ($.definition \\parser.tuple
- "Parses only within the context of a tuple's contents."
- [(tuple parser)])]
- [])))
+ [\\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.local \\parser.this_local]
+ [\\parser.foreign \\parser.this_foreign]
+ [\\parser.constant \\parser.this_constant]
+ ))
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Branch')
- ($.definition /.Match')
- ($.definition /.Environment)
- ($.definition /.Analysis)
- ($.definition /.Branch)
- ($.definition /.Match)
- ($.definition /.equivalence)
- ($.definition /.case)
- ($.definition /.unit)
- ($.definition /.bit)
- ($.definition /.nat)
- ($.definition /.int)
- ($.definition /.rev)
- ($.definition /.frac)
- ($.definition /.text)
- ($.definition /.no_op)
- ($.definition /.variable)
- ($.definition /.constant)
- ($.definition /.local)
- ($.definition /.foreign)
- ($.definition /.variant)
- ($.definition /.tuple)
- ($.definition /.format)
- ($.definition /.State+)
- ($.definition /.Operation)
- ($.definition /.Phase)
- ($.definition /.Handler)
- ($.definition /.Bundle)
- ($.definition /.with_source_code)
- ($.definition /.with_current_module)
- ($.definition /.with_location)
- ($.definition /.failure)
- ($.definition /.except)
- ($.definition /.assertion)
- ($.definition /.with_exception)
- ($.definition /.set_state)
- ($.definition /.set_source_code)
- ($.definition /.set_current_module)
- ($.definition /.set_location)
- ($.definition /.location)
- ($.definition /.source)
- ($.definition /.info)
- ($.definition /.state)]
- [..\\parser]))
+ ($.definition \\parser.tuple
+ "Parses only within the context of a tuple's contents."
+ [(tuple parser)])
+ )))
+
+(def .public documentation
+ (List $.Documentation)
+ (list.partial ($.module /._
+ "")
+
+ ($.definition /.Branch')
+ ($.definition /.Match')
+ ($.definition /.Environment)
+ ($.definition /.Analysis)
+ ($.definition /.Branch)
+ ($.definition /.Match)
+ ($.definition /.equivalence)
+ ($.definition /.case)
+ ($.definition /.unit)
+ ($.definition /.bit)
+ ($.definition /.nat)
+ ($.definition /.int)
+ ($.definition /.rev)
+ ($.definition /.frac)
+ ($.definition /.text)
+ ($.definition /.no_op)
+ ($.definition /.variable)
+ ($.definition /.constant)
+ ($.definition /.local)
+ ($.definition /.foreign)
+ ($.definition /.variant)
+ ($.definition /.tuple)
+ ($.definition /.format)
+ ($.definition /.State+)
+ ($.definition /.Operation)
+ ($.definition /.Phase)
+ ($.definition /.Handler)
+ ($.definition /.Bundle)
+ ($.definition /.with_source_code)
+ ($.definition /.with_current_module)
+ ($.definition /.with_location)
+ ($.definition /.failure)
+ ($.definition /.except)
+ ($.definition /.assertion)
+ ($.definition /.with_exception)
+ ($.definition /.set_state)
+ ($.definition /.set_source_code)
+ ($.definition /.set_current_module)
+ ($.definition /.set_location)
+ ($.definition /.location)
+ ($.definition /.source)
+ ($.definition /.info)
+ ($.definition /.state)
+
+ ..\\parser
+ ))
diff --git a/stdlib/source/documentation/lux/meta/compiler/language/lux/declaration.lux b/stdlib/source/documentation/lux/meta/compiler/language/lux/declaration.lux
index 3242e04cc..f50268496 100644
--- a/stdlib/source/documentation/lux/meta/compiler/language/lux/declaration.lux
+++ b/stdlib/source/documentation/lux/meta/compiler/language/lux/declaration.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text (.only \n)
@@ -10,26 +10,27 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Component)
- ($.definition /.State)
- ($.definition /.Import)
- ($.definition /.Requirements)
- ($.definition /.no_requirements)
- ($.definition /.merge_requirements)
- ($.definition /.State+)
- ($.definition /.Operation)
- ($.definition /.Phase)
- ($.definition /.Handler)
- ($.definition /.Bundle)
- ($.definition /.analysis)
- ($.definition /.synthesis)
- ($.definition /.generation)
- ($.definition /.lifted_analysis)
- ($.definition /.lifted_synthesis)
- ($.definition /.lifted_generation)
- ($.definition /.set_current_module)]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.Component)
+ ($.definition /.State)
+ ($.definition /.Import)
+ ($.definition /.Requirements)
+ ($.definition /.no_requirements)
+ ($.definition /.merge_requirements)
+ ($.definition /.State+)
+ ($.definition /.Operation)
+ ($.definition /.Phase)
+ ($.definition /.Handler)
+ ($.definition /.Bundle)
+ ($.definition /.analysis)
+ ($.definition /.synthesis)
+ ($.definition /.generation)
+ ($.definition /.lifted_analysis)
+ ($.definition /.lifted_synthesis)
+ ($.definition /.lifted_generation)
+ ($.definition /.set_current_module)
+ ))
diff --git a/stdlib/source/documentation/lux/meta/compiler/language/lux/generation.lux b/stdlib/source/documentation/lux/meta/compiler/language/lux/generation.lux
index 3c2c0de8b..28c844658 100644
--- a/stdlib/source/documentation/lux/meta/compiler/language/lux/generation.lux
+++ b/stdlib/source/documentation/lux/meta/compiler/language/lux/generation.lux
@@ -10,54 +10,55 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Buffer)
- ($.definition /.cannot_interpret)
- ($.definition /.cannot_overwrite_output)
- ($.definition /.no_buffer_for_saving_code)
- ($.definition /.Host)
- ($.definition /.State)
- ($.definition /.State+)
- ($.definition /.Operation)
- ($.definition /.Phase)
- ($.definition /.Handler)
- ($.definition /.Bundle)
- ($.definition /.Extender)
- ($.definition /.state)
- ($.definition /.empty_buffer)
- ($.definition /.with_anchor)
- ($.definition /.set_anchor)
- ($.definition /.anchor)
- ($.definition /.no_anchor)
- ($.definition /.with_buffer)
- ($.definition /.set_buffer)
- ($.definition /.buffer)
- ($.definition /.no_active_buffer)
- ($.definition /.get_registry)
- ($.definition /.set_registry)
- ($.definition /.next)
- ($.definition /.symbol)
- ($.definition /.enter_module)
- ($.definition /.module)
- ($.definition /.evaluate!)
- ($.definition /.execute!)
- ($.definition /.define!)
- ($.definition /.save!)
- ($.definition /.learn)
- ($.definition /.learn_custom)
- ($.definition /.learn_analyser)
- ($.definition /.learn_synthesizer)
- ($.definition /.learn_generator)
- ($.definition /.learn_declaration)
- ($.definition /.unknown_definition)
- ($.definition /.remember)
- ($.definition /.no_context)
- ($.definition /.module_id)
- ($.definition /.context)
- ($.definition /.with_context)
- ($.definition /.with_new_context)
- ($.definition /.log!)]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.Buffer)
+ ($.definition /.cannot_interpret)
+ ($.definition /.cannot_overwrite_output)
+ ($.definition /.no_buffer_for_saving_code)
+ ($.definition /.Host)
+ ($.definition /.State)
+ ($.definition /.State+)
+ ($.definition /.Operation)
+ ($.definition /.Phase)
+ ($.definition /.Handler)
+ ($.definition /.Bundle)
+ ($.definition /.Extender)
+ ($.definition /.state)
+ ($.definition /.empty_buffer)
+ ($.definition /.with_anchor)
+ ($.definition /.set_anchor)
+ ($.definition /.anchor)
+ ($.definition /.no_anchor)
+ ($.definition /.with_buffer)
+ ($.definition /.set_buffer)
+ ($.definition /.buffer)
+ ($.definition /.no_active_buffer)
+ ($.definition /.get_registry)
+ ($.definition /.set_registry)
+ ($.definition /.next)
+ ($.definition /.symbol)
+ ($.definition /.enter_module)
+ ($.definition /.module)
+ ($.definition /.evaluate!)
+ ($.definition /.execute!)
+ ($.definition /.define!)
+ ($.definition /.save!)
+ ($.definition /.learn)
+ ($.definition /.learn_custom)
+ ($.definition /.learn_analyser)
+ ($.definition /.learn_synthesizer)
+ ($.definition /.learn_generator)
+ ($.definition /.learn_declaration)
+ ($.definition /.unknown_definition)
+ ($.definition /.remember)
+ ($.definition /.no_context)
+ ($.definition /.module_id)
+ ($.definition /.context)
+ ($.definition /.with_context)
+ ($.definition /.with_new_context)
+ ($.definition /.log!)
+ ))
diff --git a/stdlib/source/documentation/lux/meta/compiler/language/lux/synthesis.lux b/stdlib/source/documentation/lux/meta/compiler/language/lux/synthesis.lux
index 3ddafebcc..b74515da2 100644
--- a/stdlib/source/documentation/lux/meta/compiler/language/lux/synthesis.lux
+++ b/stdlib/source/documentation/lux/meta/compiler/language/lux/synthesis.lux
@@ -14,129 +14,134 @@
[\\library
["[0]" /]])
-(`` (.def \\parser
- (.List $.Module)
- ($.module \\parser._
- ""
- [($.definition \\parser.cannot_parse)
- ($.definition \\parser.unconsumed_input)
- ($.definition \\parser.expected_empty_input)
- ($.definition \\parser.wrong_arity)
- ($.definition \\parser.empty_input)
-
- ($.definition (\\parser.Parser it)
- "A parser for the Lux compiler's synthesis nodes using during optimization.")
-
- ($.definition \\parser.result
- (format "Executes the parser against the inputs."
- \n "Ensures all inputs are consumed by the parser.")
- [(result parser input)])
-
- ($.definition \\parser.any
- "Yields a synthesis node without subjecting it to any analysis.")
-
- ($.definition \\parser.end
- "Ensures there are no more inputs.")
-
- ($.definition \\parser.end?
- "Checks whether there are no more inputs.")
-
- (,, (with_template [<query> <assertion>]
- [($.definition <query>
- (format "Queries for a " (template.text [<query>]) " synthesis node."))
- ($.definition <assertion>
- (format "Checks for a specific " (template.text [<query>]) " synthesis node."))]
-
- [\\parser.bit \\parser.this_bit]
- [\\parser.i64 \\parser.this_i64]
- [\\parser.f64 \\parser.this_f64]
- [\\parser.text \\parser.this_text]
- [\\parser.local \\parser.this_local]
- [\\parser.foreign \\parser.this_foreign]
- [\\parser.constant \\parser.this_constant]
- ))
-
- ($.definition \\parser.tuple
- "Parses the contents of a tuple."
- [(tuple parser)])
-
- ($.definition \\parser.function
- "Parses the body of a function with the 'expected' arity."
- [(function expected parser)])
-
- ($.definition \\parser.loop
- "Parses the initial values and the body of a loop."
- [(loop init_parsers iteration_parser)])]
- [])))
-
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Resolver)
- ($.definition /.State)
- ($.definition /.fresh_resolver)
- ($.definition /.init)
- ($.definition /.Fork)
- ($.definition /.Path')
- ($.definition /.Abstraction')
- ($.definition /.Apply')
- ($.definition /.Branch)
- ($.definition /.Scope)
- ($.definition /.Loop)
- ($.definition /.Function)
- ($.definition /.Control)
- ($.definition /.Synthesis)
- ($.definition /.State+)
- ($.definition /.Operation)
- ($.definition /.Phase)
- ($.definition /.Handler)
- ($.definition /.Bundle)
- ($.definition /.Path)
- ($.definition /.path/pop)
- ($.definition /.path/side)
- ($.definition /.path/member)
- ($.definition /.side/left)
- ($.definition /.side/right)
- ($.definition /.member/left)
- ($.definition /.member/right)
- ($.definition /.path/bind)
- ($.definition /.path/then)
- ($.definition /.path/alt)
- ($.definition /.path/seq)
- ($.definition /.Abstraction)
- ($.definition /.Apply)
- ($.definition /.unit)
- ($.definition /.with_locals)
- ($.definition /.locals)
- ($.definition /.with_currying?)
- ($.definition /.currying?)
- ($.definition /.with_new_local)
- ($.definition /.bit)
- ($.definition /.i64)
- ($.definition /.f64)
- ($.definition /.text)
- ($.definition /.variant)
- ($.definition /.tuple)
- ($.definition /.variable)
- ($.definition /.constant)
- ($.definition /.variable/local)
- ($.definition /.variable/foreign)
- ($.definition /.branch/case)
- ($.definition /.branch/let)
- ($.definition /.branch/if)
- ($.definition /.branch/get)
- ($.definition /.loop/again)
- ($.definition /.loop/scope)
- ($.definition /.function/abstraction)
- ($.definition /.function/apply)
- ($.definition /.%path')
- ($.definition /.%synthesis)
- ($.definition /.%path)
- ($.definition /.equivalence)
- ($.definition /.hash)
- ($.definition /.!bind_top)
- ($.definition /.!multi_pop)
- ($.definition /.simple_left_side)
- ($.definition /.simple_right_side)]
- [..\\parser]))
+(`` (def \\parser
+ (List $.Documentation)
+ (list ($.module \\parser._
+ "")
+
+ ($.definition \\parser.cannot_parse)
+ ($.definition \\parser.unconsumed_input)
+ ($.definition \\parser.expected_empty_input)
+ ($.definition \\parser.wrong_arity)
+ ($.definition \\parser.empty_input)
+
+ ($.definition (\\parser.Parser it)
+ "A parser for the Lux compiler's synthesis nodes using during optimization.")
+
+ ($.definition \\parser.result
+ (format "Executes the parser against the inputs."
+ \n "Ensures all inputs are consumed by the parser.")
+ [(result parser input)])
+
+ ($.definition \\parser.any
+ "Yields a synthesis node without subjecting it to any analysis.")
+
+ ($.definition \\parser.end
+ "Ensures there are no more inputs.")
+
+ ($.definition \\parser.end?
+ "Checks whether there are no more inputs.")
+
+ (,, (with_template [<query> <assertion>]
+ [($.definition <query>
+ (format "Queries for a " (template.text [<query>]) " synthesis node."))
+ ($.definition <assertion>
+ (format "Checks for a specific " (template.text [<query>]) " synthesis node."))]
+
+ [\\parser.bit \\parser.this_bit]
+ [\\parser.i64 \\parser.this_i64]
+ [\\parser.f64 \\parser.this_f64]
+ [\\parser.text \\parser.this_text]
+ [\\parser.local \\parser.this_local]
+ [\\parser.foreign \\parser.this_foreign]
+ [\\parser.constant \\parser.this_constant]
+ ))
+
+ ($.definition \\parser.tuple
+ "Parses the contents of a tuple."
+ [(tuple parser)])
+
+ ($.definition \\parser.function
+ "Parses the body of a function with the 'expected' arity."
+ [(function expected parser)])
+
+ ($.definition \\parser.loop
+ "Parses the initial values and the body of a loop."
+ [(loop init_parsers iteration_parser)])
+ )))
+
+(def .public documentation
+ (List $.Documentation)
+ (list.partial ($.module /._
+ "")
+
+ ($.definition /.Resolver)
+ ($.definition /.State)
+ ($.definition /.fresh_resolver)
+ ($.definition /.init)
+ ($.definition /.Fork)
+ ($.definition /.Path')
+ ($.definition /.Abstraction')
+ ($.definition /.Apply')
+ ($.definition /.Branch)
+ ($.definition /.Scope)
+ ($.definition /.Loop)
+ ($.definition /.Function)
+ ($.definition /.Control)
+ ($.definition /.Synthesis)
+ ($.definition /.State+)
+ ($.definition /.Operation)
+ ($.definition /.Phase)
+ ($.definition /.Handler)
+ ($.definition /.Bundle)
+ ($.definition /.Path)
+ ($.definition /.path/pop)
+ ($.definition /.path/side)
+ ($.definition /.path/member)
+ ($.definition /.side/left)
+ ($.definition /.side/right)
+ ($.definition /.member/left)
+ ($.definition /.member/right)
+ ($.definition /.path/bind)
+ ($.definition /.path/then)
+ ($.definition /.path/alt)
+ ($.definition /.path/seq)
+ ($.definition /.Abstraction)
+ ($.definition /.Apply)
+ ($.definition /.unit)
+ ($.definition /.with_locals)
+ ($.definition /.locals)
+ ($.definition /.with_currying?)
+ ($.definition /.currying?)
+ ($.definition /.with_new_local)
+ ($.definition /.bit)
+ ($.definition /.i64)
+ ($.definition /.f64)
+ ($.definition /.text)
+ ($.definition /.variant)
+ ($.definition /.tuple)
+ ($.definition /.variable)
+ ($.definition /.constant)
+ ($.definition /.variable/local)
+ ($.definition /.variable/foreign)
+ ($.definition /.branch/case)
+ ($.definition /.branch/let)
+ ($.definition /.branch/if)
+ ($.definition /.branch/get)
+ ($.definition /.loop/again)
+ ($.definition /.loop/scope)
+ ($.definition /.function/abstraction)
+ ($.definition /.function/apply)
+ ($.definition /.%path')
+ ($.definition /.%synthesis)
+ ($.definition /.%path)
+ ($.definition /.equivalence)
+ ($.definition /.hash)
+ ($.definition /.!bind_top)
+ ($.definition /.!multi_pop)
+ ($.definition /.simple_left_side)
+ ($.definition /.simple_right_side)
+
+
+ ..\\parser
+ ))
diff --git a/stdlib/source/documentation/lux/meta/compiler/phase.lux b/stdlib/source/documentation/lux/meta/compiler/phase.lux
index 84a898c31..fe549b6c9 100644
--- a/stdlib/source/documentation/lux/meta/compiler/phase.lux
+++ b/stdlib/source/documentation/lux/meta/compiler/phase.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text (.only \n)
@@ -10,23 +10,24 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Operation)
- ($.definition /.monad)
- ($.definition /.Phase)
- ($.definition /.Wrapper)
- ($.definition /.result')
- ($.definition /.result)
- ($.definition /.state)
- ($.definition /.with)
- ($.definition /.sub)
- ($.definition /.failure)
- ($.definition /.except)
- ($.definition /.lifted)
- ($.definition /.assertion)
- ($.definition /.identity)
- ($.definition /.composite)]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.Operation)
+ ($.definition /.monad)
+ ($.definition /.Phase)
+ ($.definition /.Wrapper)
+ ($.definition /.result')
+ ($.definition /.result)
+ ($.definition /.state)
+ ($.definition /.with)
+ ($.definition /.sub)
+ ($.definition /.failure)
+ ($.definition /.except)
+ ($.definition /.lifted)
+ ($.definition /.assertion)
+ ($.definition /.identity)
+ ($.definition /.composite)
+ ))
diff --git a/stdlib/source/documentation/lux/meta/extension.lux b/stdlib/source/documentation/lux/meta/extension.lux
index 737d19387..e0ce6b4b0 100644
--- a/stdlib/source/documentation/lux/meta/extension.lux
+++ b/stdlib/source/documentation/lux/meta/extension.lux
@@ -22,29 +22,30 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.analysis
- "Mechanism for defining extensions to Lux's analysis/type-checking infrastructure."
- [(analysis ("my analysis" self phase archive [pass_through <code>.any])
- (phase archive pass_through))])
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition /.synthesis
- "Mechanism for defining extensions to Lux's synthesis/optimization infrastructure."
- [(synthesis ("my synthesis" self phase archive [pass_through <analysis>.any])
- (phase archive pass_through))])
+ ($.definition /.analysis
+ "Mechanism for defining extensions to Lux's analysis/type-checking infrastructure."
+ [(analysis ("my analysis" self phase archive [pass_through <code>.any])
+ (phase archive pass_through))])
- ($.definition /.generation
- ""
- [(generation ("my generation" self phase archive [pass_through <synthesis>.any])
- (phase archive pass_through))])
+ ($.definition /.synthesis
+ "Mechanism for defining extensions to Lux's synthesis/optimization infrastructure."
+ [(synthesis ("my synthesis" self phase archive [pass_through <analysis>.any])
+ (phase archive pass_through))])
- ($.definition /.declaration
- ""
- [(declaration ("my declaration" self phase archive [parameters (<>.some <code>.any)])
- (do phase.monad
- [.let [_ (debug.log! (format "Successfully installed declaration " (%.text self) "!"))]]
- (in declaration.no_requirements)))])]
- []))
+ ($.definition /.generation
+ ""
+ [(generation ("my generation" self phase archive [pass_through <synthesis>.any])
+ (phase archive pass_through))])
+
+ ($.definition /.declaration
+ ""
+ [(declaration ("my declaration" self phase archive [parameters (<>.some <code>.any)])
+ (do phase.monad
+ [.let [_ (debug.log! (format "Successfully installed declaration " (%.text self) "!"))]]
+ (in declaration.no_requirements)))])
+ ))
diff --git a/stdlib/source/documentation/lux/meta/location.lux b/stdlib/source/documentation/lux/meta/location.lux
index 9f587ef9e..e7e7ef30a 100644
--- a/stdlib/source/documentation/lux/meta/location.lux
+++ b/stdlib/source/documentation/lux/meta/location.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except private)
+ [lux (.except)
["$" documentation]
[data
["[0]" text (.only \n)
@@ -8,19 +8,20 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.equivalence)
- ($.definition /.dummy)
- ($.definition /.format)
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition /.here
- "The Location of the current form."
- [(here)])
+ ($.definition /.equivalence)
+ ($.definition /.dummy)
+ ($.definition /.format)
- ($.definition /.with
- ""
- [(with location error)])]
- []))
+ ($.definition /.here
+ "The Location of the current form."
+ [(here)])
+
+ ($.definition /.with
+ ""
+ [(with location error)])
+ ))
diff --git a/stdlib/source/documentation/lux/meta/macro.lux b/stdlib/source/documentation/lux/meta/macro.lux
index 204efdd8c..bde4fd2f4 100644
--- a/stdlib/source/documentation/lux/meta/macro.lux
+++ b/stdlib/source/documentation/lux/meta/macro.lux
@@ -1,12 +1,12 @@
(.require
[library
- [lux (.except char symbol)
+ [lux (.except)
["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]
[collection
- ["[0]" list]]]]]
+ ["[0]" list (.use "[1]#[0]" monoid)]]]]]
["[0]" /
["[1][0]" local]
["[1][0]" syntax]
@@ -14,87 +14,91 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [... ($.definition /.single_expansion
- ... (format "Given code that requires applying a macro, does it once and returns the result."
- ... \n "Otherwise, returns the code as-is.")
- ... [(single_expansion syntax)])
+(def .public documentation
+ (List $.Documentation)
+ (list.partial ($.module /._
+ "")
- ... ($.definition /.expansion
- ... (format "Given code that requires applying a macro, expands repeatedly until no more direct macro-calls are left."
- ... \n "Otherwise, returns the code as-is.")
- ... [(expansion syntax)])
+ ... ($.definition /.single_expansion
+ ... (format "Given code that requires applying a macro, does it once and returns the result."
+ ... \n "Otherwise, returns the code as-is.")
+ ... [(single_expansion syntax)])
- ... ($.definition /.full_expansion
- ... "Expands all macro-calls everywhere recursively, until only primitive/base code remains."
- ... [(full_expansion syntax)])
+ ... ($.definition /.expansion
+ ... (format "Given code that requires applying a macro, expands repeatedly until no more direct macro-calls are left."
+ ... \n "Otherwise, returns the code as-is.")
+ ... [(expansion syntax)])
- ($.definition /.symbol
- (format "Generates a unique name as a Code node (ready to be used in code templates)."
- \n "A prefix can be given (or just be empty text) to better identify the code for debugging purposes.")
- [(symbol prefix)])
+ ... ($.definition /.full_expansion
+ ... "Expands all macro-calls everywhere recursively, until only primitive/base code remains."
+ ... [(full_expansion syntax)])
- ($.definition /.wrong_syntax_error
- "A generic error message for macro syntax failures.")
+ ($.definition /.symbol
+ (format "Generates a unique name as a Code node (ready to be used in code templates)."
+ \n "A prefix can be given (or just be empty text) to better identify the code for debugging purposes.")
+ [(symbol prefix)])
- ($.definition /.with_symbols
- "Creates new symbols and offers them to the body expression."
- [(def synchronized
- (syntax (_ [lock any
- body any])
- (with_symbols [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))))))))])
+ ($.definition /.wrong_syntax_error
+ "A generic error message for macro syntax failures.")
- ... ($.definition /.one_expansion
- ... "Works just like expand, except that it ensures that the output is a single Code token."
- ... [(one_expansion token)])
+ ($.definition /.with_symbols
+ "Creates new symbols and offers them to the body expression."
+ [(def synchronized
+ (syntax (_ [lock any
+ body any])
+ (with_symbols [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))))))))])
- ... ($.definition /.log_single_expansion!
- ... (format "Performs a macro-expansion and logs the resulting code."
- ... \n "You can either use the resulting code, or omit them."
- ... \n "By omitting them, this macro produces nothing (just like the lux.comment macro).")
- ... [(log_single_expansion!
- ... (def (foo bar baz)
- ... (-> Int Int Int)
- ... (int.+ bar baz)))
- ... (log_single_expansion! "omit"
- ... (def (foo bar baz)
- ... (-> Int Int Int)
- ... (int.+ bar baz)))])
+ ... ($.definition /.one_expansion
+ ... "Works just like expand, except that it ensures that the output is a single Code token."
+ ... [(one_expansion token)])
- ... ($.definition /.log_expansion!
- ... (format "Performs a macro-expansion and logs the resulting code."
- ... \n "You can either use the resulting code, or omit them."
- ... \n "By omitting them, this macro produces nothing (just like the lux.comment macro).")
- ... [(log_expansion!
- ... (def (foo bar baz)
- ... (-> Int Int Int)
- ... (int.+ bar baz)))
- ... (log_expansion! "omit"
- ... (def (foo bar baz)
- ... (-> Int Int Int)
- ... (int.+ bar baz)))])
+ ... ($.definition /.log_single_expansion!
+ ... (format "Performs a macro-expansion and logs the resulting code."
+ ... \n "You can either use the resulting code, or omit them."
+ ... \n "By omitting them, this macro produces nothing (just like the lux.comment macro).")
+ ... [(log_single_expansion!
+ ... (def (foo bar baz)
+ ... (-> Int Int Int)
+ ... (int.+ bar baz)))
+ ... (log_single_expansion! "omit"
+ ... (def (foo bar baz)
+ ... (-> Int Int Int)
+ ... (int.+ bar baz)))])
- ... ($.definition /.log_full_expansion!
- ... (format "Performs a macro-expansion and logs the resulting code."
- ... \n "You can either use the resulting code, or omit them."
- ... \n "By omitting them, this macro produces nothing (just like the lux.comment macro).")
- ... [(log_full_expansion!
- ... (def (foo bar baz)
- ... (-> Int Int Int)
- ... (int.+ bar baz)))
- ... (log_full_expansion! "omit"
- ... (def (foo bar baz)
- ... (-> Int Int Int)
- ... (int.+ bar baz)))])
- ]
- [/local.documentation
- /syntax.documentation
- /template.documentation]))
+ ... ($.definition /.log_expansion!
+ ... (format "Performs a macro-expansion and logs the resulting code."
+ ... \n "You can either use the resulting code, or omit them."
+ ... \n "By omitting them, this macro produces nothing (just like the lux.comment macro).")
+ ... [(log_expansion!
+ ... (def (foo bar baz)
+ ... (-> Int Int Int)
+ ... (int.+ bar baz)))
+ ... (log_expansion! "omit"
+ ... (def (foo bar baz)
+ ... (-> Int Int Int)
+ ... (int.+ bar baz)))])
+
+ ... ($.definition /.log_full_expansion!
+ ... (format "Performs a macro-expansion and logs the resulting code."
+ ... \n "You can either use the resulting code, or omit them."
+ ... \n "By omitting them, this macro produces nothing (just like the lux.comment macro).")
+ ... [(log_full_expansion!
+ ... (def (foo bar baz)
+ ... (-> Int Int Int)
+ ... (int.+ bar baz)))
+ ... (log_full_expansion! "omit"
+ ... (def (foo bar baz)
+ ... (-> Int Int Int)
+ ... (int.+ bar baz)))])
+
+ (all list#composite
+ /local.documentation
+ /syntax.documentation
+ /template.documentation
+ )
+ ))
diff --git a/stdlib/source/documentation/lux/meta/macro/local.lux b/stdlib/source/documentation/lux/meta/macro/local.lux
index 8c2ccb00c..47248b372 100644
--- a/stdlib/source/documentation/lux/meta/macro/local.lux
+++ b/stdlib/source/documentation/lux/meta/macro/local.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text (.only \n)
@@ -10,18 +10,19 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.unknown_module)
- ($.definition /.cannot_shadow_definition)
- ($.definition /.unknown_definition)
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition /.push
- (format "Installs macros in the compiler-state, with the given names."
- \n "Yields code that can be placed either as expression or as declarations."
- \n "This code un-installs the macros."
- \n "NOTE: Always use this code once to clean-up..")
- [(push macros)])]
- []))
+ ($.definition /.unknown_module)
+ ($.definition /.cannot_shadow_definition)
+ ($.definition /.unknown_definition)
+
+ ($.definition /.push
+ (format "Installs macros in the compiler-state, with the given names."
+ \n "Yields code that can be placed either as expression or as declarations."
+ \n "This code un-installs the macros."
+ \n "NOTE: Always use this code once to clean-up..")
+ [(push macros)])
+ ))
diff --git a/stdlib/source/documentation/lux/meta/macro/syntax.lux b/stdlib/source/documentation/lux/meta/macro/syntax.lux
index 4e3001f3f..4f924ea38 100644
--- a/stdlib/source/documentation/lux/meta/macro/syntax.lux
+++ b/stdlib/source/documentation/lux/meta/macro/syntax.lux
@@ -1,12 +1,12 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]
[collection
- ["[0]" list]]]]]
+ ["[0]" list (.use "[1]#[0]" monoid)]]]]]
["[0]" /
["[1][0]" check]
["[1][0]" declaration]
@@ -18,31 +18,36 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.syntax
- (format \n "A more advanced way to define macros than 'macro'."
- \n "The inputs to the macro can be parsed in complex ways through the use of syntax parsers."
- \n "The macro body is also (implicitly) run in the Meta monad, to save some typing."
- \n "Also, the compiler state can be accessed through a special binding.")
- [(def .public object
- (syntax (_ lux_state [.let [imports (class_imports lux_state)]
- .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 (all text#composite "anon-class:"
- (spaced (list (super_class_decl$ (maybe.else object_super_class super))
- (with_brackets (spaced (list#each super_class_decl$ interfaces)))
- (with_brackets (spaced (list#each constructor_arg$ constructor_args)))
- (with_brackets (spaced (list#each (method_def$ id) methods))))))]
- (in (list (` ((, (code.text def_code)))))))))])]
- [/check.documentation
- /declaration.documentation
- /definition.documentation
- /export.documentation
- /input.documentation
- /type/variable.documentation]))
+(def .public documentation
+ (List $.Documentation)
+ (list.partial ($.module /._
+ "")
+
+ ($.definition /.syntax
+ (format \n "A more advanced way to define macros than 'macro'."
+ \n "The inputs to the macro can be parsed in complex ways through the use of syntax parsers."
+ \n "The macro body is also (implicitly) run in the Meta monad, to save some typing."
+ \n "Also, the compiler state can be accessed through a special binding.")
+ [(def .public object
+ (syntax (_ lux_state [.let [imports (class_imports lux_state)]
+ .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 (all text#composite "anon-class:"
+ (spaced (list (super_class_decl$ (maybe.else object_super_class super))
+ (with_brackets (spaced (list#each super_class_decl$ interfaces)))
+ (with_brackets (spaced (list#each constructor_arg$ constructor_args)))
+ (with_brackets (spaced (list#each (method_def$ id) methods))))))]
+ (in (list (` ((, (code.text def_code)))))))))])
+
+ (all list#composite
+ /check.documentation
+ /declaration.documentation
+ /definition.documentation
+ /export.documentation
+ /input.documentation
+ /type/variable.documentation
+ )
+ ))
diff --git a/stdlib/source/documentation/lux/meta/macro/syntax/check.lux b/stdlib/source/documentation/lux/meta/macro/syntax/check.lux
index a793bb3e3..9fd16bda6 100644
--- a/stdlib/source/documentation/lux/meta/macro/syntax/check.lux
+++ b/stdlib/source/documentation/lux/meta/macro/syntax/check.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text
@@ -10,14 +10,15 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.equivalence)
- ($.definition /.format)
- ($.definition /.parser)
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition /.Check
- "A type annotation for an expression.")]
- []))
+ ($.definition /.equivalence)
+ ($.definition /.format)
+ ($.definition /.parser)
+
+ ($.definition /.Check
+ "A type annotation for an expression.")
+ ))
diff --git a/stdlib/source/documentation/lux/meta/macro/syntax/declaration.lux b/stdlib/source/documentation/lux/meta/macro/syntax/declaration.lux
index 07dd4ddc3..77290d620 100644
--- a/stdlib/source/documentation/lux/meta/macro/syntax/declaration.lux
+++ b/stdlib/source/documentation/lux/meta/macro/syntax/declaration.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text
@@ -10,19 +10,20 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.equivalence)
- ($.definition /.format)
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition /.Declaration
- "A declaration for either a constant or a function.")
+ ($.definition /.equivalence)
+ ($.definition /.format)
- ($.definition /.parser
- "A parser for declaration syntax."
- ["Such as:"
- quux
- (foo bar baz)])]
- []))
+ ($.definition /.Declaration
+ "A declaration for either a constant or a function.")
+
+ ($.definition /.parser
+ "A parser for declaration syntax."
+ ["Such as:"
+ quux
+ (foo bar baz)])
+ ))
diff --git a/stdlib/source/documentation/lux/meta/macro/syntax/definition.lux b/stdlib/source/documentation/lux/meta/macro/syntax/definition.lux
index 9434e3cf6..e429ba035 100644
--- a/stdlib/source/documentation/lux/meta/macro/syntax/definition.lux
+++ b/stdlib/source/documentation/lux/meta/macro/syntax/definition.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except Definition)
+ [lux (.except)
["$" documentation]
[data
[text
@@ -10,22 +10,23 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.equivalence)
- ($.definition /.lacks_type)
- ($.definition /.format)
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition /.Definition
- "Syntax for a constant definition.")
+ ($.definition /.equivalence)
+ ($.definition /.lacks_type)
+ ($.definition /.format)
- ($.definition /.parser
- "A reader that first macro-expands and then analyses the input Code, to ensure it is a definition."
- [(parser compiler)])
+ ($.definition /.Definition
+ "Syntax for a constant definition.")
- ($.definition /.typed
- "Only works for typed definitions."
- [(typed compiler)])]
- []))
+ ($.definition /.parser
+ "A reader that first macro-expands and then analyses the input Code, to ensure it is a definition."
+ [(parser compiler)])
+
+ ($.definition /.typed
+ "Only works for typed definitions."
+ [(typed compiler)])
+ ))
diff --git a/stdlib/source/documentation/lux/meta/macro/syntax/export.lux b/stdlib/source/documentation/lux/meta/macro/syntax/export.lux
index 2ebed7afa..f436ac551 100644
--- a/stdlib/source/documentation/lux/meta/macro/syntax/export.lux
+++ b/stdlib/source/documentation/lux/meta/macro/syntax/export.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text
@@ -10,13 +10,14 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- "Syntax for marking a definition as an export."
- [($.definition /.default_policy)
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "Syntax for marking a definition as an export.")
- ($.definition /.parser
- ""
- [(parser un_exported)])]
- []))
+ ($.definition /.default_policy)
+
+ ($.definition /.parser
+ ""
+ [(parser un_exported)])
+ ))
diff --git a/stdlib/source/documentation/lux/meta/macro/syntax/input.lux b/stdlib/source/documentation/lux/meta/macro/syntax/input.lux
index b0e2507da..cab9bd39b 100644
--- a/stdlib/source/documentation/lux/meta/macro/syntax/input.lux
+++ b/stdlib/source/documentation/lux/meta/macro/syntax/input.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text
@@ -10,16 +10,17 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.equivalence)
- ($.definition /.format)
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition /.Input
- "The common typed-argument syntax used by many macros.")
+ ($.definition /.equivalence)
+ ($.definition /.format)
- ($.definition /.parser
- "Parser for the common typed-argument syntax used by many macros.")]
- []))
+ ($.definition /.Input
+ "The common typed-argument syntax used by many macros.")
+
+ ($.definition /.parser
+ "Parser for the common typed-argument syntax used by many macros.")
+ ))
diff --git a/stdlib/source/documentation/lux/meta/macro/syntax/type/variable.lux b/stdlib/source/documentation/lux/meta/macro/syntax/type/variable.lux
index 5c5e1144a..a8a7bd52a 100644
--- a/stdlib/source/documentation/lux/meta/macro/syntax/type/variable.lux
+++ b/stdlib/source/documentation/lux/meta/macro/syntax/type/variable.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text
@@ -10,16 +10,17 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.equivalence)
- ($.definition /.format)
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition /.Variable
- "A variable's name.")
+ ($.definition /.equivalence)
+ ($.definition /.format)
- ($.definition /.parser
- "Parser for the common type variable/parameter used by many macros.")]
- []))
+ ($.definition /.Variable
+ "A variable's name.")
+
+ ($.definition /.parser
+ "Parser for the common type variable/parameter used by many macros.")
+ ))
diff --git a/stdlib/source/documentation/lux/meta/macro/template.lux b/stdlib/source/documentation/lux/meta/macro/template.lux
index bbeafc367..4ef001ef4 100644
--- a/stdlib/source/documentation/lux/meta/macro/template.lux
+++ b/stdlib/source/documentation/lux/meta/macro/template.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except let symbol)
+ [lux (.except)
["$" documentation]
[data
[text (.only \n)
@@ -10,56 +10,57 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- "Utilities commonly used while templating."
- [($.definition /.irregular_arguments)
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "Utilities commonly used while templating.")
- ($.definition /.spliced
- ""
- [(spliced [a b c d])
- "=>"
- a
- b
- c
- d])
+ ($.definition /.irregular_arguments)
- ($.definition /.amount
- ""
- [(amount [a b c d])
- "=>"
- 4])
+ ($.definition /.spliced
+ ""
+ [(spliced [a b c d])
+ "=>"
+ a
+ b
+ c
+ d])
- ($.definition /.with_locals
- "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"])
+ ($.definition /.amount
+ ""
+ [(amount [a b c d])
+ "=>"
+ 4])
- ($.definition /.text
- "A text literal made by concatenating pieces of code."
- [(text [#0 123 +456 +789.0 "abc" .def ..ghi])
- "=>"
- "#0123+456+789.0abcdefghi"])
+ ($.definition /.with_locals
+ "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"])
- ($.definition /.symbol
- (format "An symbol made by concatenating pieces of code."
- \n "The (optional) module part and the short part are specified independently.")
- [(symbol ["abc" .def ..ghi])
- "=>"
- abcdefghi]
- [(symbol [.def] ["abc" .def ..ghi])
- "=>"
- .abcdefghi])
+ ($.definition /.text
+ "A text literal made by concatenating pieces of code."
+ [(text [#0 123 +456 +789.0 "abc" .def ..ghi])
+ "=>"
+ "#0123+456+789.0abcdefghi"])
- ($.definition /.let
- "Lexically-bound templates."
- [(let [(!square <root>)
- [(* <root> <root>)]]
- (def (square root)
- (-> Nat Nat)
- (!square root)))])]
- []))
+ ($.definition /.symbol
+ (format "An symbol made by concatenating pieces of code."
+ \n "The (optional) module part and the short part are specified independently.")
+ [(symbol ["abc" .def ..ghi])
+ "=>"
+ abcdefghi]
+ [(symbol [.def] ["abc" .def ..ghi])
+ "=>"
+ .abcdefghi])
+
+ ($.definition /.let
+ "Lexically-bound templates."
+ [(let [(!square <root>)
+ [(* <root> <root>)]]
+ (def (square root)
+ (-> Nat Nat)
+ (!square root)))])
+ ))
diff --git a/stdlib/source/documentation/lux/meta/static.lux b/stdlib/source/documentation/lux/meta/static.lux
index 585cec44f..51853785a 100644
--- a/stdlib/source/documentation/lux/meta/static.lux
+++ b/stdlib/source/documentation/lux/meta/static.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except nat int rev)
+ [lux (.except)
["$" documentation]
[data
[text
@@ -10,47 +10,48 @@
[\\library
["[0]" /]])
-(`` (.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [(,, (with_template [<name> <type>]
- [($.definition <name>
- (%.code (' (<name>
- (is <type>
- (value generating expression))))))]
+(`` (def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- [/.nat .Nat]
- [/.int .Int]
- [/.rev .Rev]
- [/.frac .Frac]
- [/.text .Text]
- ))
+ (,, (with_template [<name> <type>]
+ [($.definition <name>
+ (%.code (' (<name>
+ (is <type>
+ (value generating expression))))))]
- ($.definition /.literal
- ""
- [(/.literal
- (is (-> ??? Code)
- format)
- (is ???
- (value generating expression)))])
+ [/.nat .Nat]
+ [/.int .Int]
+ [/.rev .Rev]
+ [/.frac .Frac]
+ [/.text .Text]
+ ))
- (,, (with_template [<name> <type>]
- [($.definition <name>
- (%.code (' (is <type>
- (<name>)))))]
+ ($.definition /.literal
+ ""
+ [(/.literal
+ (is (-> ??? Code)
+ format)
+ (is ???
+ (value generating expression)))])
- [/.random_nat .Nat]
- [/.random_int .Int]
- [/.random_rev .Rev]
- [/.random_frac .Frac]
- ))
+ (,, (with_template [<name> <type>]
+ [($.definition <name>
+ (%.code (' (is <type>
+ (<name>)))))]
- ($.definition /.random
- ""
- [(/.random
- (is (-> ??? Code)
- format)
- (is (Random ???)
- (random data generator)))])]
- [])))
+ [/.random_nat .Nat]
+ [/.random_int .Int]
+ [/.random_rev .Rev]
+ [/.random_frac .Frac]
+ ))
+
+ ($.definition /.random
+ ""
+ [(/.random
+ (is (-> ??? Code)
+ format)
+ (is (Random ???)
+ (random data generator)))])
+ )))
diff --git a/stdlib/source/documentation/lux/meta/symbol.lux b/stdlib/source/documentation/lux/meta/symbol.lux
index ae3ac84dd..66d24ef9b 100644
--- a/stdlib/source/documentation/lux/meta/symbol.lux
+++ b/stdlib/source/documentation/lux/meta/symbol.lux
@@ -8,18 +8,19 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.hash)
- ($.definition /.equivalence)
- ($.definition /.order)
- ($.definition /.codec)
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition /.module
- "The module part of a symbol.")
+ ($.definition /.hash)
+ ($.definition /.equivalence)
+ ($.definition /.order)
+ ($.definition /.codec)
- ($.definition /.short
- "The short part of a symbol.")]
- []))
+ ($.definition /.module
+ "The module part of a symbol.")
+
+ ($.definition /.short
+ "The short part of a symbol.")
+ ))
diff --git a/stdlib/source/documentation/lux/meta/target.lux b/stdlib/source/documentation/lux/meta/target.lux
index 8b3676d7f..4c027dabe 100644
--- a/stdlib/source/documentation/lux/meta/target.lux
+++ b/stdlib/source/documentation/lux/meta/target.lux
@@ -1,12 +1,12 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]
[collection
- ["[0]" list]]]]]
+ ["[0]" list (.use "[1]#[0]" monoid)]]]]]
[\\library
["[0]" /]]
["[0]" /
@@ -16,26 +16,31 @@
["[1][0]" python]
["[1][0]" ruby]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.old)
- ($.definition /.js)
- ($.definition /.jvm)
- ($.definition /.lua)
- ($.definition /.python)
- ($.definition /.ruby)
- ($.definition /.common_lisp)
- ($.definition /.php)
- ($.definition /.r)
- ($.definition /.scheme)
+(def .public documentation
+ (List $.Documentation)
+ (list.partial ($.module /._
+ "")
- ($.definition /.Target
- (format "The name/ID of a platform targetted by a Lux compiler."
- \n "This information can be used to generate code targetting specific platforms, and to make programs cross-platform."))]
- [/js.documentation
- /jvm/type.documentation
- /lua.documentation
- /python.documentation
- /ruby.documentation]))
+ ($.definition /.old)
+ ($.definition /.js)
+ ($.definition /.jvm)
+ ($.definition /.lua)
+ ($.definition /.python)
+ ($.definition /.ruby)
+ ($.definition /.common_lisp)
+ ($.definition /.php)
+ ($.definition /.r)
+ ($.definition /.scheme)
+
+ ($.definition /.Target
+ (format "The name/ID of a platform targetted by a Lux compiler."
+ \n "This information can be used to generate code targetting specific platforms, and to make programs cross-platform."))
+
+ (all list#composite
+ /js.documentation
+ /jvm/type.documentation
+ /lua.documentation
+ /python.documentation
+ /ruby.documentation
+ )
+ ))
diff --git a/stdlib/source/documentation/lux/meta/target/js.lux b/stdlib/source/documentation/lux/meta/target/js.lux
index 2668e038f..b52e937f0 100644
--- a/stdlib/source/documentation/lux/meta/target/js.lux
+++ b/stdlib/source/documentation/lux/meta/target/js.lux
@@ -10,88 +10,89 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Code)
- ($.definition /.code)
- ($.definition /.Expression)
- ($.definition /.Computation)
- ($.definition /.Location)
- ($.definition /.Statement)
- ($.definition /.Var)
- ($.definition /.Access)
- ($.definition /.Literal)
- ($.definition /.Loop)
- ($.definition /.Label)
- ($.definition /.null)
- ($.definition /.undefined)
- ($.definition /.boolean)
- ($.definition /.number)
- ($.definition /.string)
- ($.definition /.array)
- ($.definition /.var)
- ($.definition /.at)
- ($.definition /.the)
- ($.definition /.apply)
- ($.definition /.do)
- ($.definition /.object)
- ($.definition /.,)
- ($.definition /.then)
- ($.definition /.function_definition)
- ($.definition /.function)
- ($.definition /.closure)
- ($.definition /.=)
- ($.definition /.<)
- ($.definition /.<=)
- ($.definition /.>)
- ($.definition /.>=)
- ($.definition /.+)
- ($.definition /.-)
- ($.definition /.*)
- ($.definition /./)
- ($.definition /.%)
- ($.definition /.left_shift)
- ($.definition /.arithmetic_right_shift)
- ($.definition /.logic_right_shift)
- ($.definition /.or)
- ($.definition /.and)
- ($.definition /.bit_xor)
- ($.definition /.bit_or)
- ($.definition /.bit_and)
- ($.definition /.not)
- ($.definition /.bit_not)
- ($.definition /.opposite)
- ($.definition /.to_i32)
- ($.definition /.i32)
- ($.definition /.int)
- ($.definition /.?)
- ($.definition /.type_of)
- ($.definition /.new)
- ($.definition /.statement)
- ($.definition /.use_strict)
- ($.definition /.declare)
- ($.definition /.define)
- ($.definition /.set)
- ($.definition /.throw)
- ($.definition /.return)
- ($.definition /.delete)
- ($.definition /.if)
- ($.definition /.when)
- ($.definition /.while)
- ($.definition /.do_while)
- ($.definition /.try)
- ($.definition /.for)
- ($.definition /.label)
- ($.definition /.with_label)
- ($.definition /.break)
- ($.definition /.break_at)
- ($.definition /.continue)
- ($.definition /.continue_at)
- ($.definition /.++)
- ($.definition /.--)
- ($.definition /.comment)
- ($.definition /.switch)
- ($.definition /.not_a_number?)]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.Code)
+ ($.definition /.code)
+ ($.definition /.Expression)
+ ($.definition /.Computation)
+ ($.definition /.Location)
+ ($.definition /.Statement)
+ ($.definition /.Var)
+ ($.definition /.Access)
+ ($.definition /.Literal)
+ ($.definition /.Loop)
+ ($.definition /.Label)
+ ($.definition /.null)
+ ($.definition /.undefined)
+ ($.definition /.boolean)
+ ($.definition /.number)
+ ($.definition /.string)
+ ($.definition /.array)
+ ($.definition /.var)
+ ($.definition /.at)
+ ($.definition /.the)
+ ($.definition /.apply)
+ ($.definition /.do)
+ ($.definition /.object)
+ ($.definition /.,)
+ ($.definition /.then)
+ ($.definition /.function_definition)
+ ($.definition /.function)
+ ($.definition /.closure)
+ ($.definition /.=)
+ ($.definition /.<)
+ ($.definition /.<=)
+ ($.definition /.>)
+ ($.definition /.>=)
+ ($.definition /.+)
+ ($.definition /.-)
+ ($.definition /.*)
+ ($.definition /./)
+ ($.definition /.%)
+ ($.definition /.left_shift)
+ ($.definition /.arithmetic_right_shift)
+ ($.definition /.logic_right_shift)
+ ($.definition /.or)
+ ($.definition /.and)
+ ($.definition /.bit_xor)
+ ($.definition /.bit_or)
+ ($.definition /.bit_and)
+ ($.definition /.not)
+ ($.definition /.bit_not)
+ ($.definition /.opposite)
+ ($.definition /.to_i32)
+ ($.definition /.i32)
+ ($.definition /.int)
+ ($.definition /.?)
+ ($.definition /.type_of)
+ ($.definition /.new)
+ ($.definition /.statement)
+ ($.definition /.use_strict)
+ ($.definition /.declare)
+ ($.definition /.define)
+ ($.definition /.set)
+ ($.definition /.throw)
+ ($.definition /.return)
+ ($.definition /.delete)
+ ($.definition /.if)
+ ($.definition /.when)
+ ($.definition /.while)
+ ($.definition /.do_while)
+ ($.definition /.try)
+ ($.definition /.for)
+ ($.definition /.label)
+ ($.definition /.with_label)
+ ($.definition /.break)
+ ($.definition /.break_at)
+ ($.definition /.continue)
+ ($.definition /.continue_at)
+ ($.definition /.++)
+ ($.definition /.--)
+ ($.definition /.comment)
+ ($.definition /.switch)
+ ($.definition /.not_a_number?)
+ ))
diff --git a/stdlib/source/documentation/lux/meta/target/jvm/type.lux b/stdlib/source/documentation/lux/meta/target/jvm/type.lux
index 4b0705c7e..88d11d15b 100644
--- a/stdlib/source/documentation/lux/meta/target/jvm/type.lux
+++ b/stdlib/source/documentation/lux/meta/target/jvm/type.lux
@@ -1,12 +1,12 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]
[collection
- ["[0]" list]]]]]
+ ["[0]" list (.use "[1]#[0]" monoid)]]]]]
[\\library
["[0]" /]]
["[0]" /
@@ -19,46 +19,51 @@
["[1][0]" reflection]
["[1][0]" signature]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Type)
- ($.definition /.Argument)
- ($.definition /.Typed)
- ($.definition /.Constraint)
- ($.definition /.signature)
- ($.definition /.descriptor)
- ($.definition /.reflection)
- ($.definition /.void)
- ($.definition /.boolean)
- ($.definition /.byte)
- ($.definition /.short)
- ($.definition /.int)
- ($.definition /.long)
- ($.definition /.float)
- ($.definition /.double)
- ($.definition /.char)
- ($.definition /.array)
- ($.definition /.class)
- ($.definition /.declaration)
- ($.definition /.as_class)
- ($.definition /.wildcard)
- ($.definition /.var)
- ($.definition /.lower)
- ($.definition /.upper)
- ($.definition /.method)
- ($.definition /.equivalence)
- ($.definition /.hash)
- ($.definition /.primitive?)
- ($.definition /.void?)
- ($.definition /.class?)
- ($.definition /.format)]
- [/alias.documentation
- /box.documentation
- /category.documentation
- /descriptor.documentation
- /lux.documentation
- /parser.documentation
- /reflection.documentation
- /signature.documentation]))
+(def .public documentation
+ (List $.Documentation)
+ (list.partial ($.module /._
+ "")
+
+ ($.definition /.Type)
+ ($.definition /.Argument)
+ ($.definition /.Typed)
+ ($.definition /.Constraint)
+ ($.definition /.signature)
+ ($.definition /.descriptor)
+ ($.definition /.reflection)
+ ($.definition /.void)
+ ($.definition /.boolean)
+ ($.definition /.byte)
+ ($.definition /.short)
+ ($.definition /.int)
+ ($.definition /.long)
+ ($.definition /.float)
+ ($.definition /.double)
+ ($.definition /.char)
+ ($.definition /.array)
+ ($.definition /.class)
+ ($.definition /.declaration)
+ ($.definition /.as_class)
+ ($.definition /.wildcard)
+ ($.definition /.var)
+ ($.definition /.lower)
+ ($.definition /.upper)
+ ($.definition /.method)
+ ($.definition /.equivalence)
+ ($.definition /.hash)
+ ($.definition /.primitive?)
+ ($.definition /.void?)
+ ($.definition /.class?)
+ ($.definition /.format)
+
+ (all list#composite
+ /alias.documentation
+ /box.documentation
+ /category.documentation
+ /descriptor.documentation
+ /lux.documentation
+ /parser.documentation
+ /reflection.documentation
+ /signature.documentation
+ )
+ ))
diff --git a/stdlib/source/documentation/lux/meta/target/jvm/type/alias.lux b/stdlib/source/documentation/lux/meta/target/jvm/type/alias.lux
index a95f2515a..7d9ea965e 100644
--- a/stdlib/source/documentation/lux/meta/target/jvm/type/alias.lux
+++ b/stdlib/source/documentation/lux/meta/target/jvm/type/alias.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text (.only \n)
@@ -10,11 +10,12 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Aliasing)
- ($.definition /.fresh)
- ($.definition /.method)]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.Aliasing)
+ ($.definition /.fresh)
+ ($.definition /.method)
+ ))
diff --git a/stdlib/source/documentation/lux/meta/target/jvm/type/box.lux b/stdlib/source/documentation/lux/meta/target/jvm/type/box.lux
index 55bb96b15..bd38778f6 100644
--- a/stdlib/source/documentation/lux/meta/target/jvm/type/box.lux
+++ b/stdlib/source/documentation/lux/meta/target/jvm/type/box.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text (.only \n)
@@ -10,16 +10,17 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.boolean)
- ($.definition /.byte)
- ($.definition /.short)
- ($.definition /.int)
- ($.definition /.long)
- ($.definition /.float)
- ($.definition /.double)
- ($.definition /.char)]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.boolean)
+ ($.definition /.byte)
+ ($.definition /.short)
+ ($.definition /.int)
+ ($.definition /.long)
+ ($.definition /.float)
+ ($.definition /.double)
+ ($.definition /.char)
+ ))
diff --git a/stdlib/source/documentation/lux/meta/target/jvm/type/category.lux b/stdlib/source/documentation/lux/meta/target/jvm/type/category.lux
index 670dd0b25..91bdb26ad 100644
--- a/stdlib/source/documentation/lux/meta/target/jvm/type/category.lux
+++ b/stdlib/source/documentation/lux/meta/target/jvm/type/category.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text (.only \n)
@@ -10,21 +10,22 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Method)
- ($.definition /.Return')
- ($.definition /.Value')
- ($.definition /.Return)
- ($.definition /.Value)
- ($.definition /.Void)
- ($.definition /.Object)
- ($.definition /.Parameter)
- ($.definition /.Primitive)
- ($.definition /.Var)
- ($.definition /.Class)
- ($.definition /.Array)
- ($.definition /.Declaration)]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.Method)
+ ($.definition /.Return')
+ ($.definition /.Value')
+ ($.definition /.Return)
+ ($.definition /.Value)
+ ($.definition /.Void)
+ ($.definition /.Object)
+ ($.definition /.Parameter)
+ ($.definition /.Primitive)
+ ($.definition /.Var)
+ ($.definition /.Class)
+ ($.definition /.Array)
+ ($.definition /.Declaration)
+ ))
diff --git a/stdlib/source/documentation/lux/meta/target/jvm/type/descriptor.lux b/stdlib/source/documentation/lux/meta/target/jvm/type/descriptor.lux
index 7df3c49e6..750c40b5f 100644
--- a/stdlib/source/documentation/lux/meta/target/jvm/type/descriptor.lux
+++ b/stdlib/source/documentation/lux/meta/target/jvm/type/descriptor.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text (.only \n)
@@ -10,33 +10,34 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Descriptor)
- ($.definition /.descriptor)
- ($.definition /.void)
- ($.definition /.boolean)
- ($.definition /.byte)
- ($.definition /.short)
- ($.definition /.int)
- ($.definition /.long)
- ($.definition /.float)
- ($.definition /.double)
- ($.definition /.char)
- ($.definition /.class_prefix)
- ($.definition /.class_suffix)
- ($.definition /.class)
- ($.definition /.declaration)
- ($.definition /.as_class)
- ($.definition /.var)
- ($.definition /.wildcard)
- ($.definition /.lower)
- ($.definition /.upper)
- ($.definition /.array_prefix)
- ($.definition /.array)
- ($.definition /.method)
- ($.definition /.equivalence)
- ($.definition /.class_name)]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.Descriptor)
+ ($.definition /.descriptor)
+ ($.definition /.void)
+ ($.definition /.boolean)
+ ($.definition /.byte)
+ ($.definition /.short)
+ ($.definition /.int)
+ ($.definition /.long)
+ ($.definition /.float)
+ ($.definition /.double)
+ ($.definition /.char)
+ ($.definition /.class_prefix)
+ ($.definition /.class_suffix)
+ ($.definition /.class)
+ ($.definition /.declaration)
+ ($.definition /.as_class)
+ ($.definition /.var)
+ ($.definition /.wildcard)
+ ($.definition /.lower)
+ ($.definition /.upper)
+ ($.definition /.array_prefix)
+ ($.definition /.array)
+ ($.definition /.method)
+ ($.definition /.equivalence)
+ ($.definition /.class_name)
+ ))
diff --git a/stdlib/source/documentation/lux/meta/target/jvm/type/lux.lux b/stdlib/source/documentation/lux/meta/target/jvm/type/lux.lux
index 12f08046b..4d50fc0f2 100644
--- a/stdlib/source/documentation/lux/meta/target/jvm/type/lux.lux
+++ b/stdlib/source/documentation/lux/meta/target/jvm/type/lux.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text (.only \n)
@@ -10,19 +10,20 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Lower)
- ($.definition /.Upper)
- ($.definition /.Mapping)
- ($.definition /.fresh)
- ($.definition /.unknown_var)
- ($.definition /.class)
- ($.definition /.type)
- ($.definition /.boxed_type)
- ($.definition /.return)
- ($.definition /.boxed_return)
- ($.definition /.check)]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.Lower)
+ ($.definition /.Upper)
+ ($.definition /.Mapping)
+ ($.definition /.fresh)
+ ($.definition /.unknown_var)
+ ($.definition /.class)
+ ($.definition /.type)
+ ($.definition /.boxed_type)
+ ($.definition /.return)
+ ($.definition /.boxed_return)
+ ($.definition /.check)
+ ))
diff --git a/stdlib/source/documentation/lux/meta/target/jvm/type/parser.lux b/stdlib/source/documentation/lux/meta/target/jvm/type/parser.lux
index e647e1a81..d80d68c2b 100644
--- a/stdlib/source/documentation/lux/meta/target/jvm/type/parser.lux
+++ b/stdlib/source/documentation/lux/meta/target/jvm/type/parser.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text (.only \n)
@@ -10,44 +10,45 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.void)
- ($.definition /.boolean)
- ($.definition /.byte)
- ($.definition /.short)
- ($.definition /.int)
- ($.definition /.long)
- ($.definition /.float)
- ($.definition /.double)
- ($.definition /.char)
- ($.definition /.wildcard)
- ($.definition /.primitive)
- ($.definition /.class_name)
- ($.definition /.var_name)
- ($.definition /.var')
- ($.definition /.var)
- ($.definition /.var?)
- ($.definition /.name)
- ($.definition /.parameter)
- ($.definition /.array')
- ($.definition /.class)
- ($.definition /.lower?)
- ($.definition /.upper?)
- ($.definition /.read_class)
- ($.definition /.value)
- ($.definition /.array)
- ($.definition /.object)
- ($.definition /.return)
- ($.definition /.method)
- ($.definition /.array?)
- ($.definition /.class?)
- ($.definition /.primitive?)
- ($.definition /.wildcard?)
- ($.definition /.parameter?)
- ($.definition /.object?)
- ($.definition /.declaration')
- ($.definition /.declaration)]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.void)
+ ($.definition /.boolean)
+ ($.definition /.byte)
+ ($.definition /.short)
+ ($.definition /.int)
+ ($.definition /.long)
+ ($.definition /.float)
+ ($.definition /.double)
+ ($.definition /.char)
+ ($.definition /.wildcard)
+ ($.definition /.primitive)
+ ($.definition /.class_name)
+ ($.definition /.var_name)
+ ($.definition /.var')
+ ($.definition /.var)
+ ($.definition /.var?)
+ ($.definition /.name)
+ ($.definition /.parameter)
+ ($.definition /.array')
+ ($.definition /.class)
+ ($.definition /.lower?)
+ ($.definition /.upper?)
+ ($.definition /.read_class)
+ ($.definition /.value)
+ ($.definition /.array)
+ ($.definition /.object)
+ ($.definition /.return)
+ ($.definition /.method)
+ ($.definition /.array?)
+ ($.definition /.class?)
+ ($.definition /.primitive?)
+ ($.definition /.wildcard?)
+ ($.definition /.parameter?)
+ ($.definition /.object?)
+ ($.definition /.declaration')
+ ($.definition /.declaration)
+ ))
diff --git a/stdlib/source/documentation/lux/meta/target/jvm/type/reflection.lux b/stdlib/source/documentation/lux/meta/target/jvm/type/reflection.lux
index 4ffeb078b..9439e0b2b 100644
--- a/stdlib/source/documentation/lux/meta/target/jvm/type/reflection.lux
+++ b/stdlib/source/documentation/lux/meta/target/jvm/type/reflection.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text (.only \n)
@@ -10,28 +10,29 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Reflection)
- ($.definition /.reflection)
- ($.definition /.equivalence)
- ($.definition /.void)
- ($.definition /.boolean)
- ($.definition /.byte)
- ($.definition /.short)
- ($.definition /.int)
- ($.definition /.long)
- ($.definition /.float)
- ($.definition /.double)
- ($.definition /.char)
- ($.definition /.class)
- ($.definition /.declaration)
- ($.definition /.as_class)
- ($.definition /.array)
- ($.definition /.var)
- ($.definition /.wildcard)
- ($.definition /.lower)
- ($.definition /.upper)]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.Reflection)
+ ($.definition /.reflection)
+ ($.definition /.equivalence)
+ ($.definition /.void)
+ ($.definition /.boolean)
+ ($.definition /.byte)
+ ($.definition /.short)
+ ($.definition /.int)
+ ($.definition /.long)
+ ($.definition /.float)
+ ($.definition /.double)
+ ($.definition /.char)
+ ($.definition /.class)
+ ($.definition /.declaration)
+ ($.definition /.as_class)
+ ($.definition /.array)
+ ($.definition /.var)
+ ($.definition /.wildcard)
+ ($.definition /.lower)
+ ($.definition /.upper)
+ ))
diff --git a/stdlib/source/documentation/lux/meta/target/jvm/type/signature.lux b/stdlib/source/documentation/lux/meta/target/jvm/type/signature.lux
index f7454baf0..fea7063e4 100644
--- a/stdlib/source/documentation/lux/meta/target/jvm/type/signature.lux
+++ b/stdlib/source/documentation/lux/meta/target/jvm/type/signature.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text (.only \n)
@@ -10,39 +10,40 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Signature)
- ($.definition /.signature)
- ($.definition /.void)
- ($.definition /.boolean)
- ($.definition /.byte)
- ($.definition /.short)
- ($.definition /.int)
- ($.definition /.long)
- ($.definition /.float)
- ($.definition /.double)
- ($.definition /.char)
- ($.definition /.array)
- ($.definition /.wildcard)
- ($.definition /.var_prefix)
- ($.definition /.var)
- ($.definition /.var_name)
- ($.definition /.lower_prefix)
- ($.definition /.upper_prefix)
- ($.definition /.lower)
- ($.definition /.upper)
- ($.definition /.parameters_start)
- ($.definition /.parameters_end)
- ($.definition /.class)
- ($.definition /.declaration)
- ($.definition /.as_class)
- ($.definition /.arguments_start)
- ($.definition /.arguments_end)
- ($.definition /.exception_prefix)
- ($.definition /.method)
- ($.definition /.equivalence)
- ($.definition /.hash)]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.Signature)
+ ($.definition /.signature)
+ ($.definition /.void)
+ ($.definition /.boolean)
+ ($.definition /.byte)
+ ($.definition /.short)
+ ($.definition /.int)
+ ($.definition /.long)
+ ($.definition /.float)
+ ($.definition /.double)
+ ($.definition /.char)
+ ($.definition /.array)
+ ($.definition /.wildcard)
+ ($.definition /.var_prefix)
+ ($.definition /.var)
+ ($.definition /.var_name)
+ ($.definition /.lower_prefix)
+ ($.definition /.upper_prefix)
+ ($.definition /.lower)
+ ($.definition /.upper)
+ ($.definition /.parameters_start)
+ ($.definition /.parameters_end)
+ ($.definition /.class)
+ ($.definition /.declaration)
+ ($.definition /.as_class)
+ ($.definition /.arguments_start)
+ ($.definition /.arguments_end)
+ ($.definition /.exception_prefix)
+ ($.definition /.method)
+ ($.definition /.equivalence)
+ ($.definition /.hash)
+ ))
diff --git a/stdlib/source/documentation/lux/meta/target/lua.lux b/stdlib/source/documentation/lux/meta/target/lua.lux
index 34bd530d3..8d7b66680 100644
--- a/stdlib/source/documentation/lux/meta/target/lua.lux
+++ b/stdlib/source/documentation/lux/meta/target/lua.lux
@@ -10,83 +10,84 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Code)
- ($.definition /.equivalence)
- ($.definition /.hash)
- ($.definition /.manual)
- ($.definition /.code)
- ($.definition /.Expression)
- ($.definition /.Computation)
- ($.definition /.Location)
- ($.definition /.Statement)
- ($.definition /.Literal)
- ($.definition /.Var)
- ($.definition /.Access)
- ($.definition /.Label)
- ($.definition /.nil)
- ($.definition /.boolean)
- ($.definition /.int)
- ($.definition /.float)
- ($.definition /.string)
- ($.definition /.multi)
- ($.definition /.array)
- ($.definition /.table)
- ($.definition /.item)
- ($.definition /.the)
- ($.definition /.length)
- ($.definition /.apply)
- ($.definition /.do)
- ($.definition /.=)
- ($.definition /.<)
- ($.definition /.<=)
- ($.definition /.>)
- ($.definition /.>=)
- ($.definition /.+)
- ($.definition /.-)
- ($.definition /.*)
- ($.definition /.^)
- ($.definition /./)
- ($.definition /.//)
- ($.definition /.%)
- ($.definition /.concat)
- ($.definition /.or)
- ($.definition /.and)
- ($.definition /.bit_or)
- ($.definition /.bit_and)
- ($.definition /.bit_xor)
- ($.definition /.bit_shl)
- ($.definition /.bit_shr)
- ($.definition /.not)
- ($.definition /.opposite)
- ($.definition /.var)
- ($.definition /.label)
- ($.definition /.statement)
- ($.definition /.then)
- ($.definition /.local)
- ($.definition /.set)
- ($.definition /.let)
- ($.definition /.local/1)
- ($.definition /.if)
- ($.definition /.when)
- ($.definition /.while)
- ($.definition /.repeat)
- ($.definition /.for_in)
- ($.definition /.for_step)
- ($.definition /.return)
- ($.definition /.closure)
- ($.definition /.function)
- ($.definition /.local_function)
- ($.definition /.break)
- ($.definition /.set_label)
- ($.definition /.go_to)
- ($.definition /.error/1)
- ($.definition /.print/1)
- ($.definition /.require/1)
- ($.definition /.type/1)
- ($.definition /.ipairs/1)
- ($.definition /.error/2)]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.Code)
+ ($.definition /.equivalence)
+ ($.definition /.hash)
+ ($.definition /.manual)
+ ($.definition /.code)
+ ($.definition /.Expression)
+ ($.definition /.Computation)
+ ($.definition /.Location)
+ ($.definition /.Statement)
+ ($.definition /.Literal)
+ ($.definition /.Var)
+ ($.definition /.Access)
+ ($.definition /.Label)
+ ($.definition /.nil)
+ ($.definition /.boolean)
+ ($.definition /.int)
+ ($.definition /.float)
+ ($.definition /.string)
+ ($.definition /.multi)
+ ($.definition /.array)
+ ($.definition /.table)
+ ($.definition /.item)
+ ($.definition /.the)
+ ($.definition /.length)
+ ($.definition /.apply)
+ ($.definition /.do)
+ ($.definition /.=)
+ ($.definition /.<)
+ ($.definition /.<=)
+ ($.definition /.>)
+ ($.definition /.>=)
+ ($.definition /.+)
+ ($.definition /.-)
+ ($.definition /.*)
+ ($.definition /.^)
+ ($.definition /./)
+ ($.definition /.//)
+ ($.definition /.%)
+ ($.definition /.concat)
+ ($.definition /.or)
+ ($.definition /.and)
+ ($.definition /.bit_or)
+ ($.definition /.bit_and)
+ ($.definition /.bit_xor)
+ ($.definition /.bit_shl)
+ ($.definition /.bit_shr)
+ ($.definition /.not)
+ ($.definition /.opposite)
+ ($.definition /.var)
+ ($.definition /.label)
+ ($.definition /.statement)
+ ($.definition /.then)
+ ($.definition /.local)
+ ($.definition /.set)
+ ($.definition /.let)
+ ($.definition /.local/1)
+ ($.definition /.if)
+ ($.definition /.when)
+ ($.definition /.while)
+ ($.definition /.repeat)
+ ($.definition /.for_in)
+ ($.definition /.for_step)
+ ($.definition /.return)
+ ($.definition /.closure)
+ ($.definition /.function)
+ ($.definition /.local_function)
+ ($.definition /.break)
+ ($.definition /.set_label)
+ ($.definition /.go_to)
+ ($.definition /.error/1)
+ ($.definition /.print/1)
+ ($.definition /.require/1)
+ ($.definition /.type/1)
+ ($.definition /.ipairs/1)
+ ($.definition /.error/2)
+ ))
diff --git a/stdlib/source/documentation/lux/meta/target/python.lux b/stdlib/source/documentation/lux/meta/target/python.lux
index 952032825..50263c3b9 100644
--- a/stdlib/source/documentation/lux/meta/target/python.lux
+++ b/stdlib/source/documentation/lux/meta/target/python.lux
@@ -10,103 +10,104 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Code)
- ($.definition /.equivalence)
- ($.definition /.hash)
- ($.definition /.manual)
- ($.definition /.code)
- ($.definition /.Expression)
- ($.definition /.Computation)
- ($.definition /.Location)
- ($.definition /.Var)
- ($.definition /.Statement)
- ($.definition /.Literal)
- ($.definition /.Access)
- ($.definition /.Loop)
- ($.definition /.SVar)
- ($.definition /.Single)
- ($.definition /.PVar)
- ($.definition /.Poly)
- ($.definition /.KVar)
- ($.definition /.Keyword)
- ($.definition /.var)
- ($.definition /.poly)
- ($.definition /.keyword)
- ($.definition /.none)
- ($.definition /.bool)
- ($.definition /.int)
- ($.definition /.long)
- ($.definition /.float)
- ($.definition /.string)
- ($.definition /.unicode)
- ($.definition /.tuple)
- ($.definition /.list)
- ($.definition /.slice)
- ($.definition /.slice_from)
- ($.definition /.dict)
- ($.definition /.apply)
- ($.definition /.splat_poly)
- ($.definition /.splat_keyword)
- ($.definition /.the)
- ($.definition /.do)
- ($.definition /.item)
- ($.definition /.?)
- ($.definition /.is)
- ($.definition /.=)
- ($.definition /.<)
- ($.definition /.<=)
- ($.definition /.>)
- ($.definition /.>=)
- ($.definition /.+)
- ($.definition /.-)
- ($.definition /.*)
- ($.definition /./)
- ($.definition /.//)
- ($.definition /.%)
- ($.definition /.**)
- ($.definition /.bit_or)
- ($.definition /.bit_and)
- ($.definition /.bit_xor)
- ($.definition /.bit_shl)
- ($.definition /.bit_shr)
- ($.definition /.or)
- ($.definition /.and)
- ($.definition /.not)
- ($.definition /.opposite)
- ($.definition /.lambda)
- ($.definition /.set)
- ($.definition /.delete)
- ($.definition /.if)
- ($.definition /.when)
- ($.definition /.then)
- ($.definition /.break)
- ($.definition /.continue)
- ($.definition /.while)
- ($.definition /.for_in)
- ($.definition /.statement)
- ($.definition /.pass)
- ($.definition /.Except)
- ($.definition /.try)
- ($.definition /.raise)
- ($.definition /.return)
- ($.definition /.print)
- ($.definition /.exec)
- ($.definition /.def)
- ($.definition /.import)
- ($.definition /.comment)
- ($.definition /.str/1)
- ($.definition /.ord/1)
- ($.definition /.float/1)
- ($.definition /.int/1)
- ($.definition /.len/1)
- ($.definition /.chr/1)
- ($.definition /.unichr/1)
- ($.definition /.unicode/1)
- ($.definition /.repr/1)
- ($.definition /.__import__/1)
- ($.definition /.Exception/1)]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.Code)
+ ($.definition /.equivalence)
+ ($.definition /.hash)
+ ($.definition /.manual)
+ ($.definition /.code)
+ ($.definition /.Expression)
+ ($.definition /.Computation)
+ ($.definition /.Location)
+ ($.definition /.Var)
+ ($.definition /.Statement)
+ ($.definition /.Literal)
+ ($.definition /.Access)
+ ($.definition /.Loop)
+ ($.definition /.SVar)
+ ($.definition /.Single)
+ ($.definition /.PVar)
+ ($.definition /.Poly)
+ ($.definition /.KVar)
+ ($.definition /.Keyword)
+ ($.definition /.var)
+ ($.definition /.poly)
+ ($.definition /.keyword)
+ ($.definition /.none)
+ ($.definition /.bool)
+ ($.definition /.int)
+ ($.definition /.long)
+ ($.definition /.float)
+ ($.definition /.string)
+ ($.definition /.unicode)
+ ($.definition /.tuple)
+ ($.definition /.list)
+ ($.definition /.slice)
+ ($.definition /.slice_from)
+ ($.definition /.dict)
+ ($.definition /.apply)
+ ($.definition /.splat_poly)
+ ($.definition /.splat_keyword)
+ ($.definition /.the)
+ ($.definition /.do)
+ ($.definition /.item)
+ ($.definition /.?)
+ ($.definition /.is)
+ ($.definition /.=)
+ ($.definition /.<)
+ ($.definition /.<=)
+ ($.definition /.>)
+ ($.definition /.>=)
+ ($.definition /.+)
+ ($.definition /.-)
+ ($.definition /.*)
+ ($.definition /./)
+ ($.definition /.//)
+ ($.definition /.%)
+ ($.definition /.**)
+ ($.definition /.bit_or)
+ ($.definition /.bit_and)
+ ($.definition /.bit_xor)
+ ($.definition /.bit_shl)
+ ($.definition /.bit_shr)
+ ($.definition /.or)
+ ($.definition /.and)
+ ($.definition /.not)
+ ($.definition /.opposite)
+ ($.definition /.lambda)
+ ($.definition /.set)
+ ($.definition /.delete)
+ ($.definition /.if)
+ ($.definition /.when)
+ ($.definition /.then)
+ ($.definition /.break)
+ ($.definition /.continue)
+ ($.definition /.while)
+ ($.definition /.for_in)
+ ($.definition /.statement)
+ ($.definition /.pass)
+ ($.definition /.Except)
+ ($.definition /.try)
+ ($.definition /.raise)
+ ($.definition /.return)
+ ($.definition /.print)
+ ($.definition /.exec)
+ ($.definition /.def)
+ ($.definition /.import)
+ ($.definition /.comment)
+ ($.definition /.str/1)
+ ($.definition /.ord/1)
+ ($.definition /.float/1)
+ ($.definition /.int/1)
+ ($.definition /.len/1)
+ ($.definition /.chr/1)
+ ($.definition /.unichr/1)
+ ($.definition /.unicode/1)
+ ($.definition /.repr/1)
+ ($.definition /.__import__/1)
+ ($.definition /.Exception/1)
+ ))
diff --git a/stdlib/source/documentation/lux/meta/target/ruby.lux b/stdlib/source/documentation/lux/meta/target/ruby.lux
index 7116cb82f..d67257929 100644
--- a/stdlib/source/documentation/lux/meta/target/ruby.lux
+++ b/stdlib/source/documentation/lux/meta/target/ruby.lux
@@ -10,104 +10,105 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Code)
- ($.definition /.equivalence)
- ($.definition /.hash)
- ($.definition /.manual)
- ($.definition /.code)
- ($.definition /.Expression)
- ($.definition /.Computation)
- ($.definition /.Location)
- ($.definition /.Var)
- ($.definition /.LVar)
- ($.definition /.Statement)
- ($.definition /.Literal)
- ($.definition /.Access)
- ($.definition /.GVar)
- ($.definition /.IVar)
- ($.definition /.SVar)
- ($.definition /.LVar*)
- ($.definition /.LVar**)
- ($.definition /.global)
- ($.definition /.instance)
- ($.definition /.static)
- ($.definition /.local)
- ($.definition /.variadic)
- ($.definition /.splat)
- ($.definition /.variadic_kv)
- ($.definition /.double_splat)
- ($.definition /.latest_error_message)
- ($.definition /.latest_error_location)
- ($.definition /.last_string_read)
- ($.definition /.last_line_number_read)
- ($.definition /.last_string_matched)
- ($.definition /.last_regexp_match)
- ($.definition /.case_insensitivity_flag)
- ($.definition /.input_record_separator)
- ($.definition /.output_record_separator)
- ($.definition /.script_name)
- ($.definition /.process_id)
- ($.definition /.exit_status)
- ($.definition /.command_line_arguments)
- ($.definition /.nil)
- ($.definition /.bool)
- ($.definition /.int)
- ($.definition /.string)
- ($.definition /.symbol)
- ($.definition /.float)
- ($.definition /.array_range)
- ($.definition /.array)
- ($.definition /.hash)
- ($.definition /.apply)
- ($.definition /.apply_lambda)
- ($.definition /.the)
- ($.definition /.item)
- ($.definition /.?)
- ($.definition /.statement)
- ($.definition /.then)
- ($.definition /.set)
- ($.definition /.if)
- ($.definition /.when)
- ($.definition /.while)
- ($.definition /.for_in)
- ($.definition /.Rescue)
- ($.definition /.begin)
- ($.definition /.catch)
- ($.definition /.return)
- ($.definition /.raise)
- ($.definition /.next)
- ($.definition /.redo)
- ($.definition /.break)
- ($.definition /.function)
- ($.definition /.lambda)
- ($.definition /.=)
- ($.definition /.<)
- ($.definition /.<=)
- ($.definition /.>)
- ($.definition /.>=)
- ($.definition /.+)
- ($.definition /.-)
- ($.definition /.*)
- ($.definition /./)
- ($.definition /.%)
- ($.definition /.pow)
- ($.definition /.or)
- ($.definition /.and)
- ($.definition /.bit_or)
- ($.definition /.bit_and)
- ($.definition /.bit_xor)
- ($.definition /.bit_shl)
- ($.definition /.bit_shr)
- ($.definition /.not)
- ($.definition /.opposite)
- ($.definition /.comment)
- ($.definition /.do)
- ($.definition /.print/1)
- ($.definition /.require/1)
- ($.definition /.print/2)
- ($.definition /.throw/1)]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.Code)
+ ($.definition /.equivalence)
+ ($.definition /.hash)
+ ($.definition /.manual)
+ ($.definition /.code)
+ ($.definition /.Expression)
+ ($.definition /.Computation)
+ ($.definition /.Location)
+ ($.definition /.Var)
+ ($.definition /.LVar)
+ ($.definition /.Statement)
+ ($.definition /.Literal)
+ ($.definition /.Access)
+ ($.definition /.GVar)
+ ($.definition /.IVar)
+ ($.definition /.SVar)
+ ($.definition /.LVar*)
+ ($.definition /.LVar**)
+ ($.definition /.global)
+ ($.definition /.instance)
+ ($.definition /.static)
+ ($.definition /.local)
+ ($.definition /.variadic)
+ ($.definition /.splat)
+ ($.definition /.variadic_kv)
+ ($.definition /.double_splat)
+ ($.definition /.latest_error_message)
+ ($.definition /.latest_error_location)
+ ($.definition /.last_string_read)
+ ($.definition /.last_line_number_read)
+ ($.definition /.last_string_matched)
+ ($.definition /.last_regexp_match)
+ ($.definition /.case_insensitivity_flag)
+ ($.definition /.input_record_separator)
+ ($.definition /.output_record_separator)
+ ($.definition /.script_name)
+ ($.definition /.process_id)
+ ($.definition /.exit_status)
+ ($.definition /.command_line_arguments)
+ ($.definition /.nil)
+ ($.definition /.bool)
+ ($.definition /.int)
+ ($.definition /.string)
+ ($.definition /.symbol)
+ ($.definition /.float)
+ ($.definition /.array_range)
+ ($.definition /.array)
+ ($.definition /.hash)
+ ($.definition /.apply)
+ ($.definition /.apply_lambda)
+ ($.definition /.the)
+ ($.definition /.item)
+ ($.definition /.?)
+ ($.definition /.statement)
+ ($.definition /.then)
+ ($.definition /.set)
+ ($.definition /.if)
+ ($.definition /.when)
+ ($.definition /.while)
+ ($.definition /.for_in)
+ ($.definition /.Rescue)
+ ($.definition /.begin)
+ ($.definition /.catch)
+ ($.definition /.return)
+ ($.definition /.raise)
+ ($.definition /.next)
+ ($.definition /.redo)
+ ($.definition /.break)
+ ($.definition /.function)
+ ($.definition /.lambda)
+ ($.definition /.=)
+ ($.definition /.<)
+ ($.definition /.<=)
+ ($.definition /.>)
+ ($.definition /.>=)
+ ($.definition /.+)
+ ($.definition /.-)
+ ($.definition /.*)
+ ($.definition /./)
+ ($.definition /.%)
+ ($.definition /.pow)
+ ($.definition /.or)
+ ($.definition /.and)
+ ($.definition /.bit_or)
+ ($.definition /.bit_and)
+ ($.definition /.bit_xor)
+ ($.definition /.bit_shl)
+ ($.definition /.bit_shr)
+ ($.definition /.not)
+ ($.definition /.opposite)
+ ($.definition /.comment)
+ ($.definition /.do)
+ ($.definition /.print/1)
+ ($.definition /.require/1)
+ ($.definition /.print/2)
+ ($.definition /.throw/1)
+ ))
diff --git a/stdlib/source/documentation/lux/meta/type.lux b/stdlib/source/documentation/lux/meta/type.lux
index b0736757a..4e2d13faa 100644
--- a/stdlib/source/documentation/lux/meta/type.lux
+++ b/stdlib/source/documentation/lux/meta/type.lux
@@ -4,7 +4,9 @@
["$" documentation]
[data
["[0]" text (.only \n)
- ["%" \\format (.only format)]]]
+ ["%" \\format (.only format)]]
+ [collection
+ ["[0]" list (.use "[1]#[0]" monoid)]]]
[meta
[macro
["[0]" template]]]]]
@@ -23,251 +25,257 @@
["[1][0]" unit]
["[1][0]" variance]])
-(`` (.def \\parser
- (.List $.Module)
- ($.module \\parser._
- (format "Parsing of Lux types."
- \n "Used mostly for polytypic programming.")
- [($.definition \\parser.not_existential)
- ($.definition \\parser.not_recursive)
- ($.definition \\parser.not_named)
- ($.definition \\parser.not_parameter)
- ($.definition \\parser.unknown_parameter)
- ($.definition \\parser.not_function)
- ($.definition \\parser.not_application)
- ($.definition \\parser.not_polymorphic)
- ($.definition \\parser.not_variant)
- ($.definition \\parser.not_tuple)
- ($.definition \\parser.types_do_not_match)
- ($.definition \\parser.wrong_parameter)
- ($.definition \\parser.empty_input)
- ($.definition \\parser.unconsumed_input)
- ($.definition \\parser.parameter)
- ($.definition \\parser.recursive_self)
- ($.definition \\parser.recursive_call)
-
- ($.definition \\parser.Env
- "An environment for type parsing.")
-
- ($.definition (\\parser.Parser it)
- "A parser of Lux types.")
-
- ($.definition \\parser.fresh
- "An empty parsing environment.")
-
- ($.definition \\parser.result
- (format "Applies a parser against a type."
- \n "Verifies that the parser fully consumes the type's information.")
- [(result poly type)])
-
- ($.definition \\parser.env
- "Yields the current parsing environment.")
-
- ($.definition \\parser.next
- "Inspect a type in the input stream without consuming it.")
-
- ($.definition \\parser.any
- "Yields a type, without examination.")
-
- ($.definition \\parser.local
- "Apply a parser to the given inputs."
- [(local types poly)])
-
- ($.definition \\parser.with_extension
- ""
- [(with_extension type poly)])
-
- (,, (with_template [<name>]
- [(`` ($.definition <name>
- (format "Parses the contents of a " (,, (template.text [<name>])) " type.")))]
-
- [\\parser.variant]
- [\\parser.tuple]
- ))
-
- ($.definition \\parser.polymorphic
- ""
- [(polymorphic poly)])
-
- ($.definition \\parser.function
- "Parses a function's inputs and output."
- [(function in_poly out_poly)])
-
- ($.definition \\parser.applied
- "Parses a type application."
- [(applied poly)])
-
- (,, (with_template [<name> <doc>]
- [($.definition <name>
- <doc>)]
-
- [\\parser.exactly "Parses a type exactly."]
- [\\parser.sub "Parses a sub type."]
- [\\parser.super "Parses a super type."]
- ))
-
- ($.definition \\parser.argument
- ""
- [(argument env idx)])
-
- ($.definition \\parser.this_parameter
- ""
- [(this_parameter id)])
-
- ($.definition \\parser.existential
- "Yields an existential type.")
-
- ($.definition \\parser.named
- "Yields a named type.")
-
- ($.definition \\parser.recursive
- ""
- [(recursive poly)])]
- [])))
-
-(`` (.def .public documentation
- (.List $.Module)
- ($.module /._
- "Basic functionality for working with types."
- [($.definition /.equivalence)
-
- (,, (with_template [<name>]
- [($.definition <name>
- "The number of parameters, and the body, of a quantified type.")]
-
- [/.flat_univ_q]
- [/.flat_ex_q]
- ))
-
- ($.definition /.flat_function
- "The input, and the output of a function type."
- [(flat_function type)])
-
- ($.definition /.flat_application
- "The quantified type, and its parameters, for a type-application."
- [(flat_application type)])
-
- (,, (with_template [<name>]
- [($.definition <name>
- "The members of a composite type.")]
-
- [/.flat_variant]
- [/.flat_tuple]
- ))
-
- ($.definition /.format
- "A (readable) textual representable of a type."
- [(format type)])
-
- ($.definition /.applied
- "To the extend possible, applies a quantified type to the given parameters."
- [(applied params func)])
-
- ($.definition /.code
- (%.format "A representation of a type as code."
- \n "The code is such that evaluating it would yield the type value.")
- [(code type)])
-
- ($.definition /.de_aliased
- "A (potentially named) type that does not have its name shadowed by other names."
- [(de_aliased type)])
-
- ($.definition /.anonymous
- "A type without any names covering it."
- [(anonymous type)])
-
- (,, (with_template [<name>]
- [($.definition <name>
- "A composite type, constituted by the given member types.")]
-
- [/.variant]
- [/.tuple]
- ))
-
- ($.definition /.function
- "A function type, with the given inputs and output."
- [(function inputs output)])
-
- ($.definition /.application
- "An un-evaluated type application, with the given quantified type, and parameters."
- [(application params quant)])
-
- (,, (with_template [<name>]
- [($.definition <name>
- "A quantified type, with the given number of parameters, and body.")]
-
- [/.univ_q]
- [/.ex_q]
- ))
-
- ($.definition /.quantified?
- "Only yields #1 for universally or existentially quantified types."
- [(quantified? type)])
-
- ($.definition /.array
- "An array type, with the given level of nesting/depth, and the given element type."
- [(array depth element_type)])
-
- ($.definition /.flat_array
- "The level of nesting/depth and element type for an array type."
- [(flat_array type)])
-
- ($.definition /.array?
- "Is a type an array type?")
-
- ($.definition /.log!
- "Logs to the console/terminal the type of an expression."
- [(log! (is Foo (foo expression)))
- "=>"
- "Expression: (foo expression)"
- " Type: Foo"
- (foo expression)])
-
- ($.definition /.as
- (%.format "Casts a value to a specific type."
- \n "The specified type can depend on type variables of the original type of the value."
- \n "NOTE: Careless use of type-casts is an easy way to introduce bugs. USE WITH CAUTION.")
- [(is (Bar Bit Nat Text)
- (as [a b c]
- (Foo a [b c])
- (Bar a b c)
- (is (Foo Bit [Nat Text])
- (foo expression))))])
-
- ($.definition /.sharing
- "Allows specifing the type of an expression as sharing type-variables with the type of another expression."
- [(is (Bar Bit Nat Text)
- (sharing [a b c]
- (is (Foo a [b c])
- (is (Foo Bit [Nat Text])
- (foo expression)))
- (is (Bar a b c)
- (bar expression))))])
-
- ($.definition /.by_example
- "Constructs a type that shares type-variables with an expression of some other type."
- [(is Type
- (by_example [a b c]
- (is (Foo a [b c])
- (is (Foo Bit [Nat Text])
- (foo expression)))
- (Bar a b c)))
- "=>"
- (.type_literal (Bar Bit Nat Text))])
-
- ($.definition /.let
- "Local bindings for types."
- [(let [side (Either Int Frac)]
- (List [side side]))])]
- [..\\parser
-
- /primitive.documentation
- /check.documentation
- /dynamic.documentation
- /implicit.documentation
- /poly.documentation
- /quotient.documentation
- /refinement.documentation
- /resource.documentation
- /unit.documentation
- /variance.documentation])))
+(`` (def \\parser
+ (List $.Documentation)
+ (list ($.module \\parser._
+ (format "Parsing of Lux types."
+ \n "Used mostly for polytypic programming."))
+
+ ($.definition \\parser.not_existential)
+ ($.definition \\parser.not_recursive)
+ ($.definition \\parser.not_named)
+ ($.definition \\parser.not_parameter)
+ ($.definition \\parser.unknown_parameter)
+ ($.definition \\parser.not_function)
+ ($.definition \\parser.not_application)
+ ($.definition \\parser.not_polymorphic)
+ ($.definition \\parser.not_variant)
+ ($.definition \\parser.not_tuple)
+ ($.definition \\parser.types_do_not_match)
+ ($.definition \\parser.wrong_parameter)
+ ($.definition \\parser.empty_input)
+ ($.definition \\parser.unconsumed_input)
+ ($.definition \\parser.parameter)
+ ($.definition \\parser.recursive_self)
+ ($.definition \\parser.recursive_call)
+
+ ($.definition \\parser.Env
+ "An environment for type parsing.")
+
+ ($.definition (\\parser.Parser it)
+ "A parser of Lux types.")
+
+ ($.definition \\parser.fresh
+ "An empty parsing environment.")
+
+ ($.definition \\parser.result
+ (format "Applies a parser against a type."
+ \n "Verifies that the parser fully consumes the type's information.")
+ [(result poly type)])
+
+ ($.definition \\parser.env
+ "Yields the current parsing environment.")
+
+ ($.definition \\parser.next
+ "Inspect a type in the input stream without consuming it.")
+
+ ($.definition \\parser.any
+ "Yields a type, without examination.")
+
+ ($.definition \\parser.local
+ "Apply a parser to the given inputs."
+ [(local types poly)])
+
+ ($.definition \\parser.with_extension
+ ""
+ [(with_extension type poly)])
+
+ (,, (with_template [<name>]
+ [(`` ($.definition <name>
+ (format "Parses the contents of a " (,, (template.text [<name>])) " type.")))]
+
+ [\\parser.variant]
+ [\\parser.tuple]
+ ))
+
+ ($.definition \\parser.polymorphic
+ ""
+ [(polymorphic poly)])
+
+ ($.definition \\parser.function
+ "Parses a function's inputs and output."
+ [(function in_poly out_poly)])
+
+ ($.definition \\parser.applied
+ "Parses a type application."
+ [(applied poly)])
+
+ (,, (with_template [<name> <doc>]
+ [($.definition <name>
+ <doc>)]
+
+ [\\parser.exactly "Parses a type exactly."]
+ [\\parser.sub "Parses a sub type."]
+ [\\parser.super "Parses a super type."]
+ ))
+
+ ($.definition \\parser.argument
+ ""
+ [(argument env idx)])
+
+ ($.definition \\parser.this_parameter
+ ""
+ [(this_parameter id)])
+
+ ($.definition \\parser.existential
+ "Yields an existential type.")
+
+ ($.definition \\parser.named
+ "Yields a named type.")
+
+ ($.definition \\parser.recursive
+ ""
+ [(recursive poly)])
+ )))
+
+(`` (def .public documentation
+ (List $.Documentation)
+ (list.partial ($.module /._
+ "Basic functionality for working with types.")
+
+ ($.definition /.equivalence)
+
+ (,, (with_template [<name>]
+ [($.definition <name>
+ "The number of parameters, and the body, of a quantified type.")]
+
+ [/.flat_univ_q]
+ [/.flat_ex_q]
+ ))
+
+ ($.definition /.flat_function
+ "The input, and the output of a function type."
+ [(flat_function type)])
+
+ ($.definition /.flat_application
+ "The quantified type, and its parameters, for a type-application."
+ [(flat_application type)])
+
+ (,, (with_template [<name>]
+ [($.definition <name>
+ "The members of a composite type.")]
+
+ [/.flat_variant]
+ [/.flat_tuple]
+ ))
+
+ ($.definition /.format
+ "A (readable) textual representable of a type."
+ [(format type)])
+
+ ($.definition /.applied
+ "To the extend possible, applies a quantified type to the given parameters."
+ [(applied params func)])
+
+ ($.definition /.code
+ (%.format "A representation of a type as code."
+ \n "The code is such that evaluating it would yield the type value.")
+ [(code type)])
+
+ ($.definition /.de_aliased
+ "A (potentially named) type that does not have its name shadowed by other names."
+ [(de_aliased type)])
+
+ ($.definition /.anonymous
+ "A type without any names covering it."
+ [(anonymous type)])
+
+ (,, (with_template [<name>]
+ [($.definition <name>
+ "A composite type, constituted by the given member types.")]
+
+ [/.variant]
+ [/.tuple]
+ ))
+
+ ($.definition /.function
+ "A function type, with the given inputs and output."
+ [(function inputs output)])
+
+ ($.definition /.application
+ "An un-evaluated type application, with the given quantified type, and parameters."
+ [(application params quant)])
+
+ (,, (with_template [<name>]
+ [($.definition <name>
+ "A quantified type, with the given number of parameters, and body.")]
+
+ [/.univ_q]
+ [/.ex_q]
+ ))
+
+ ($.definition /.quantified?
+ "Only yields #1 for universally or existentially quantified types."
+ [(quantified? type)])
+
+ ($.definition /.array
+ "An array type, with the given level of nesting/depth, and the given element type."
+ [(array depth element_type)])
+
+ ($.definition /.flat_array
+ "The level of nesting/depth and element type for an array type."
+ [(flat_array type)])
+
+ ($.definition /.array?
+ "Is a type an array type?")
+
+ ($.definition /.log!
+ "Logs to the console/terminal the type of an expression."
+ [(log! (is Foo (foo expression)))
+ "=>"
+ "Expression: (foo expression)"
+ " Type: Foo"
+ (foo expression)])
+
+ ($.definition /.as
+ (%.format "Casts a value to a specific type."
+ \n "The specified type can depend on type variables of the original type of the value."
+ \n "NOTE: Careless use of type-casts is an easy way to introduce bugs. USE WITH CAUTION.")
+ [(is (Bar Bit Nat Text)
+ (as [a b c]
+ (Foo a [b c])
+ (Bar a b c)
+ (is (Foo Bit [Nat Text])
+ (foo expression))))])
+
+ ($.definition /.sharing
+ "Allows specifing the type of an expression as sharing type-variables with the type of another expression."
+ [(is (Bar Bit Nat Text)
+ (sharing [a b c]
+ (is (Foo a [b c])
+ (is (Foo Bit [Nat Text])
+ (foo expression)))
+ (is (Bar a b c)
+ (bar expression))))])
+
+ ($.definition /.by_example
+ "Constructs a type that shares type-variables with an expression of some other type."
+ [(is Type
+ (by_example [a b c]
+ (is (Foo a [b c])
+ (is (Foo Bit [Nat Text])
+ (foo expression)))
+ (Bar a b c)))
+ "=>"
+ (.type_literal (Bar Bit Nat Text))])
+
+ ($.definition /.let
+ "Local bindings for types."
+ [(let [side (Either Int Frac)]
+ (List [side side]))])
+
+ (all list#composite
+ ..\\parser
+
+ /primitive.documentation
+ /check.documentation
+ /dynamic.documentation
+ /implicit.documentation
+ /poly.documentation
+ /quotient.documentation
+ /refinement.documentation
+ /resource.documentation
+ /unit.documentation
+ /variance.documentation
+ )
+ )))
diff --git a/stdlib/source/documentation/lux/meta/type/check.lux b/stdlib/source/documentation/lux/meta/type/check.lux
index ba4009ed4..55cbfd5b1 100644
--- a/stdlib/source/documentation/lux/meta/type/check.lux
+++ b/stdlib/source/documentation/lux/meta/type/check.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except and)
+ [lux (.except)
["$" documentation]
[data
["[0]" text (.only \n)
@@ -8,70 +8,71 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- "Type-checking functionality."
- [($.definition /.unknown_type_var)
- ($.definition /.unbound_type_var)
- ($.definition /.invalid_type_application)
- ($.definition /.cannot_rebind_var)
- ($.definition /.type_check_failed)
- ($.definition /.functor)
- ($.definition /.apply)
- ($.definition /.monad)
- ($.definition /.bound?)
- ($.definition /.peek)
- ($.definition /.read)
-
- ($.definition /.Var
- "The ID for a type-variable in a type-checking context.")
-
- ($.definition (/.Check it)
- "A type-checking computation which may fail or yield a value.")
-
- ($.definition /.result
- ""
- [(result context proc)])
-
- ($.definition /.failure
- ""
- [(failure message)])
-
- ($.definition /.assertion
- ""
- [(assertion message test)])
-
- ($.definition /.except
- ""
- [(except exception message)])
-
- ($.definition /.existential
- "A brand-new existential type.")
-
- ($.definition /.bind
- (format "Attemmpts to buy a type-variable."
- \n "Fails if the variable has been bound already.")
- [(bind type id)])
-
- ($.definition /.var
- "A brand-new (unbound) type-variable.")
-
- ($.definition /.fresh_context
- "An empty/un-used type-checking context.")
-
- ($.definition /.check
- "Type-check to ensure that the 'expected' type subsumes the 'actual' type."
- [(check expected actual)])
-
- ($.definition /.subsumes?
- "A simple type-checking function that just returns a yes/no answer."
- [(subsumes? expected actual)])
-
- ($.definition /.context
- "The current state of the type-checking context.")
-
- ($.definition /.clean
- "Resolves every bound type-variable to yield a new type that is as resolved as possible."
- [(clean inputT)])]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "Type-checking functionality.")
+
+ ($.definition /.unknown_type_var)
+ ($.definition /.unbound_type_var)
+ ($.definition /.invalid_type_application)
+ ($.definition /.cannot_rebind_var)
+ ($.definition /.type_check_failed)
+ ($.definition /.functor)
+ ($.definition /.apply)
+ ($.definition /.monad)
+ ($.definition /.bound?)
+ ($.definition /.peek)
+ ($.definition /.read)
+
+ ($.definition /.Var
+ "The ID for a type-variable in a type-checking context.")
+
+ ($.definition (/.Check it)
+ "A type-checking computation which may fail or yield a value.")
+
+ ($.definition /.result
+ ""
+ [(result context proc)])
+
+ ($.definition /.failure
+ ""
+ [(failure message)])
+
+ ($.definition /.assertion
+ ""
+ [(assertion message test)])
+
+ ($.definition /.except
+ ""
+ [(except exception message)])
+
+ ($.definition /.existential
+ "A brand-new existential type.")
+
+ ($.definition /.bind
+ (format "Attemmpts to buy a type-variable."
+ \n "Fails if the variable has been bound already.")
+ [(bind type id)])
+
+ ($.definition /.var
+ "A brand-new (unbound) type-variable.")
+
+ ($.definition /.fresh_context
+ "An empty/un-used type-checking context.")
+
+ ($.definition /.check
+ "Type-check to ensure that the 'expected' type subsumes the 'actual' type."
+ [(check expected actual)])
+
+ ($.definition /.subsumes?
+ "A simple type-checking function that just returns a yes/no answer."
+ [(subsumes? expected actual)])
+
+ ($.definition /.context
+ "The current state of the type-checking context.")
+
+ ($.definition /.clean
+ "Resolves every bound type-variable to yield a new type that is as resolved as possible."
+ [(clean inputT)])
+ ))
diff --git a/stdlib/source/documentation/lux/meta/type/dynamic.lux b/stdlib/source/documentation/lux/meta/type/dynamic.lux
index 596bbb610..af54272d6 100644
--- a/stdlib/source/documentation/lux/meta/type/dynamic.lux
+++ b/stdlib/source/documentation/lux/meta/type/dynamic.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except static)
+ [lux (.except)
["$" documentation]
[data
["[0]" text (.only \n)
@@ -8,23 +8,24 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.wrong_type)
- ($.definition /.format)
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition /.Dynamic
- "A value coupled with its type, so it can be checked later.")
+ ($.definition /.wrong_type)
+ ($.definition /.format)
- ($.definition /.dynamic
- ""
- [(is Dynamic
- (dynamic 123))])
+ ($.definition /.Dynamic
+ "A value coupled with its type, so it can be checked later.")
- ($.definition /.static
- ""
- [(is (try.Try Nat)
- (static Nat (dynamic 123)))])]
- []))
+ ($.definition /.dynamic
+ ""
+ [(is Dynamic
+ (dynamic 123))])
+
+ ($.definition /.static
+ ""
+ [(is (try.Try Nat)
+ (static Nat (dynamic 123)))])
+ ))
diff --git a/stdlib/source/documentation/lux/meta/type/implicit.lux b/stdlib/source/documentation/lux/meta/type/implicit.lux
index 001435ce8..54ded8081 100644
--- a/stdlib/source/documentation/lux/meta/type/implicit.lux
+++ b/stdlib/source/documentation/lux/meta/type/implicit.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except and)
+ [lux (.except)
["$" documentation]
[data
["[0]" text (.only \n)
@@ -8,44 +8,45 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.a/an
- (format "Automatic implementation selection (for type-class style polymorphism)."
- \n "This feature layers type-class style polymorphism on top of Lux's signatures and implementations."
- \n "When calling a polymorphic function, or using a polymorphic constant,"
- \n "this macro will check the types of the arguments, and the expected type for the whole expression"
- \n "and it will search in the local scope, the module's scope and the imports' scope"
- \n "in order to find suitable implementations to satisfy those requirements."
- \n "If a single alternative is found, that one will be used automatically."
- \n "If no alternative is found, or if more than one alternative is found (ambiguity)"
- \n "a compile-time error will be raised, to alert the user."
- \n \n "Caveat emptor: You need to make sure to import the module of any implementation you want to use."
- \n "Otherwise, this macro will not find it.")
- ["Nat equivalence"
- (at number.equivalence = x y)
- (a/an = x y)]
- ["Can optionally add the prefix of the module where the signature was defined."
- (a/an equivalence.= x y)]
- ["(List Nat) equivalence"
- (a/an =
- (list.indices 10)
- (list.indices 10))]
- ["(Functor List) each"
- (a/an each ++ (list.indices 10))])
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition /.with
- "Establish lexical bindings for implementations that will be prioritized over non-lexically-bound implementations."
- [(with [n.addition]
- (n.= (at n.addition composite left right)
- (a/an composite left right)))])
+ ($.definition /.a/an
+ (format "Automatic implementation selection (for type-class style polymorphism)."
+ \n "This feature layers type-class style polymorphism on top of Lux's signatures and implementations."
+ \n "When calling a polymorphic function, or using a polymorphic constant,"
+ \n "this macro will check the types of the arguments, and the expected type for the whole expression"
+ \n "and it will search in the local scope, the module's scope and the imports' scope"
+ \n "in order to find suitable implementations to satisfy those requirements."
+ \n "If a single alternative is found, that one will be used automatically."
+ \n "If no alternative is found, or if more than one alternative is found (ambiguity)"
+ \n "a compile-time error will be raised, to alert the user."
+ \n \n "Caveat emptor: You need to make sure to import the module of any implementation you want to use."
+ \n "Otherwise, this macro will not find it.")
+ ["Nat equivalence"
+ (at number.equivalence = x y)
+ (a/an = x y)]
+ ["Can optionally add the prefix of the module where the signature was defined."
+ (a/an equivalence.= x y)]
+ ["(List Nat) equivalence"
+ (a/an =
+ (list.indices 10)
+ (list.indices 10))]
+ ["(Functor List) each"
+ (a/an each ++ (list.indices 10))])
- ($.definition /.implicitly
- "Establish local definitions for implementations that will be prioritized over foreign definitions."
- [(implicitly n.multiplication)
-
- (n.= (at n.multiplication composite left right)
- (a/an composite left right))])]
- []))
+ ($.definition /.with
+ "Establish lexical bindings for implementations that will be prioritized over non-lexically-bound implementations."
+ [(with [n.addition]
+ (n.= (at n.addition composite left right)
+ (a/an composite left right)))])
+
+ ($.definition /.implicitly
+ "Establish local definitions for implementations that will be prioritized over foreign definitions."
+ [(implicitly n.multiplication)
+
+ (n.= (at n.multiplication composite left right)
+ (a/an composite left right))])
+ ))
diff --git a/stdlib/source/documentation/lux/meta/type/poly.lux b/stdlib/source/documentation/lux/meta/type/poly.lux
index dd562c4df..fb33e6236 100644
--- a/stdlib/source/documentation/lux/meta/type/poly.lux
+++ b/stdlib/source/documentation/lux/meta/type/poly.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except and)
+ [lux (.except)
["$" documentation]
[abstract
[\\specification
@@ -12,13 +12,14 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.polytypic)
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition /.code
- ""
- [(code env type)])]
- []))
+ ($.definition /.polytypic)
+
+ ($.definition /.code
+ ""
+ [(code env type)])
+ ))
diff --git a/stdlib/source/documentation/lux/meta/type/primitive.lux b/stdlib/source/documentation/lux/meta/type/primitive.lux
index 1f042cb52..bf1ce3c83 100644
--- a/stdlib/source/documentation/lux/meta/type/primitive.lux
+++ b/stdlib/source/documentation/lux/meta/type/primitive.lux
@@ -8,111 +8,112 @@
[\\library
["[0]" /]])
-(`` (.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Frame
- "Meta-data about an abstract/nominal type in a stack of them.")
-
- ($.definition /.current
- "The currently-being-defined abstract/nominal type.")
-
- ($.definition /.specific
- "A specific abstract/nominal type still being defined somewhere in the scope."
- [(specific name)])
-
- (,, (with_template [<name> <from> <$> <to>]
- [($.definition <name>
- "Type-casting macro for abstract/nominal types."
- [(|> value
- (is <from>)
- <$>
- (is <to>))])]
-
- [/.abstraction Representation abstraction Abstraction]
- [/.representation Abstraction representation Representation]
- ))
-
- ($.definition /.primitive
- (format "Define abstract/nominal types which hide their representation details."
- \n "You can convert between the abstraction and its representation selectively to access the value, while hiding it from others.")
- [(primitive String
- Text
-
- (def (string value)
- (-> Text String)
- (abstraction value))
-
- (def (text value)
- (-> String Text)
- (representation value)))]
- ["Type-parameters are optional."
- (primitive (Duplicate a)
- [a a]
-
- (def (duplicate value)
- (All (_ a) (-> a (Duplicate a)))
- (abstraction [value value])))]
- ["Definitions can be nested."
- (primitive (Single a)
- a
-
- (def (single value)
- (All (_ a) (-> a (Single a)))
- (abstraction value))
-
- (primitive (Double a)
- [a a]
-
- (def (double value)
- (All (_ a) (-> a (Double a)))
- (abstraction [value value]))
-
- (def (single' value)
- (All (_ a) (-> a (Single a)))
- (abstraction Single [value value]))
-
- (let [value 0123]
- (same? value
- (|> value
- single'
- (representation Single)
- double
- representation)))))]
- ["Type-parameters do not necessarily have to be used in the representation type."
- "If they are not used, they become phantom types and can be used to customize types without changing the representation."
- (primitive (JavaScript a)
- Text
-
- (primitive Expression Any)
- (primitive Statement Any)
-
- (def (+ x y)
- (-> (JavaScript Expression) (JavaScript Expression) (JavaScript Expression))
- (abstraction
- (format "(" (representation x) "+" (representation y) ")")))
-
- (def (while test body)
- (-> (JavaScript Expression) (JavaScript Statement) (JavaScript Statement))
- (abstraction
- (format "while(" (representation test) ") {"
- (representation body)
- "}"))))])
-
- ($.definition /.transmutation
- "Transmutes an abstract/nominal type's phantom types."
- [(primitive (JavaScript a)
- Text
-
- (primitive Expression Any)
- (primitive Statement Any)
-
- (def (statement expression)
- (-> (JavaScript Expression) (JavaScript Statement))
- (transmutation expression))
-
- (def (statement' expression)
- (-> (JavaScript Expression) (JavaScript Statement))
- (transmutation JavaScript expression)))])]
- [])))
+(`` (def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.Frame
+ "Meta-data about an abstract/nominal type in a stack of them.")
+
+ ($.definition /.current
+ "The currently-being-defined abstract/nominal type.")
+
+ ($.definition /.specific
+ "A specific abstract/nominal type still being defined somewhere in the scope."
+ [(specific name)])
+
+ (,, (with_template [<name> <from> <$> <to>]
+ [($.definition <name>
+ "Type-casting macro for abstract/nominal types."
+ [(|> value
+ (is <from>)
+ <$>
+ (is <to>))])]
+
+ [/.abstraction Representation abstraction Abstraction]
+ [/.representation Abstraction representation Representation]
+ ))
+
+ ($.definition /.primitive
+ (format "Define abstract/nominal types which hide their representation details."
+ \n "You can convert between the abstraction and its representation selectively to access the value, while hiding it from others.")
+ [(primitive String
+ Text
+
+ (def (string value)
+ (-> Text String)
+ (abstraction value))
+
+ (def (text value)
+ (-> String Text)
+ (representation value)))]
+ ["Type-parameters are optional."
+ (primitive (Duplicate a)
+ [a a]
+
+ (def (duplicate value)
+ (All (_ a) (-> a (Duplicate a)))
+ (abstraction [value value])))]
+ ["Definitions can be nested."
+ (primitive (Single a)
+ a
+
+ (def (single value)
+ (All (_ a) (-> a (Single a)))
+ (abstraction value))
+
+ (primitive (Double a)
+ [a a]
+
+ (def (double value)
+ (All (_ a) (-> a (Double a)))
+ (abstraction [value value]))
+
+ (def (single' value)
+ (All (_ a) (-> a (Single a)))
+ (abstraction Single [value value]))
+
+ (let [value 0123]
+ (same? value
+ (|> value
+ single'
+ (representation Single)
+ double
+ representation)))))]
+ ["Type-parameters do not necessarily have to be used in the representation type."
+ "If they are not used, they become phantom types and can be used to customize types without changing the representation."
+ (primitive (JavaScript a)
+ Text
+
+ (primitive Expression Any)
+ (primitive Statement Any)
+
+ (def (+ x y)
+ (-> (JavaScript Expression) (JavaScript Expression) (JavaScript Expression))
+ (abstraction
+ (format "(" (representation x) "+" (representation y) ")")))
+
+ (def (while test body)
+ (-> (JavaScript Expression) (JavaScript Statement) (JavaScript Statement))
+ (abstraction
+ (format "while(" (representation test) ") {"
+ (representation body)
+ "}"))))])
+
+ ($.definition /.transmutation
+ "Transmutes an abstract/nominal type's phantom types."
+ [(primitive (JavaScript a)
+ Text
+
+ (primitive Expression Any)
+ (primitive Statement Any)
+
+ (def (statement expression)
+ (-> (JavaScript Expression) (JavaScript Statement))
+ (transmutation expression))
+
+ (def (statement' expression)
+ (-> (JavaScript Expression) (JavaScript Statement))
+ (transmutation JavaScript expression)))])
+ )))
diff --git a/stdlib/source/documentation/lux/meta/type/quotient.lux b/stdlib/source/documentation/lux/meta/type/quotient.lux
index 58f9edfd5..e374a11c5 100644
--- a/stdlib/source/documentation/lux/meta/type/quotient.lux
+++ b/stdlib/source/documentation/lux/meta/type/quotient.lux
@@ -8,36 +8,37 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.class)
- ($.definition /.value)
- ($.definition /.label)
- ($.definition /.equivalence)
-
- ($.definition (/.Class value label)
- "The class knows how to classify/label values that are meant to be equivalent to one another.")
-
- ($.definition (/.Quotient value label)
- (format "A quotient value has been labeled with a class."
- \n "All equivalent values will belong to the same class."
- \n "This means all equivalent values possess the same label."))
-
- ($.definition /.quotient
- ""
- [(quotient class value)])
-
- ($.definition /.type
- "The Quotient type associated with a Class type."
- [(def even
- (class even?))
-
- (def Even
- Type
- (type even))
-
- (is Even
- (quotient even 123))])]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.class)
+ ($.definition /.value)
+ ($.definition /.label)
+ ($.definition /.equivalence)
+
+ ($.definition (/.Class value label)
+ "The class knows how to classify/label values that are meant to be equivalent to one another.")
+
+ ($.definition (/.Quotient value label)
+ (format "A quotient value has been labeled with a class."
+ \n "All equivalent values will belong to the same class."
+ \n "This means all equivalent values possess the same label."))
+
+ ($.definition /.quotient
+ ""
+ [(quotient class value)])
+
+ ($.definition /.type
+ "The Quotient type associated with a Class type."
+ [(def even
+ (class even?))
+
+ (def Even
+ Type
+ (type even))
+
+ (is Even
+ (quotient even 123))])
+ ))
diff --git a/stdlib/source/documentation/lux/meta/type/refinement.lux b/stdlib/source/documentation/lux/meta/type/refinement.lux
index 7342da0dc..0b9601f1e 100644
--- a/stdlib/source/documentation/lux/meta/type/refinement.lux
+++ b/stdlib/source/documentation/lux/meta/type/refinement.lux
@@ -8,45 +8,46 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.value)
- ($.definition /.predicate)
-
- ($.definition (/.Refined it)
- "A refined version of another type, using a predicate to select valid instances.")
-
- ($.definition (/.Refiner it)
- "A selection mechanism for refined instances of a type.")
-
- ($.definition /.refiner
- ""
- [(refiner predicate)])
-
- ($.definition /.lifted
- (format "Yields a function that can work on refined values."
- \n "Respects the constraints of the refinement.")
- [(lifted transform)])
-
- ($.definition /.only
- ""
- [(only refiner values)])
-
- ($.definition /.partition
- "Separates refined values from the un-refined ones."
- [(partition refiner values)])
-
- ($.definition /.type
- "The Refined type associated with a Refiner type."
- [(def even
- (refiner even?))
-
- (def Even
- Type
- (type even))
-
- (is (Maybe Even)
- (even 123))])]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.value)
+ ($.definition /.predicate)
+
+ ($.definition (/.Refined it)
+ "A refined version of another type, using a predicate to select valid instances.")
+
+ ($.definition (/.Refiner it)
+ "A selection mechanism for refined instances of a type.")
+
+ ($.definition /.refiner
+ ""
+ [(refiner predicate)])
+
+ ($.definition /.lifted
+ (format "Yields a function that can work on refined values."
+ \n "Respects the constraints of the refinement.")
+ [(lifted transform)])
+
+ ($.definition /.only
+ ""
+ [(only refiner values)])
+
+ ($.definition /.partition
+ "Separates refined values from the un-refined ones."
+ [(partition refiner values)])
+
+ ($.definition /.type
+ "The Refined type associated with a Refiner type."
+ [(def even
+ (refiner even?))
+
+ (def Even
+ Type
+ (type even))
+
+ (is (Maybe Even)
+ (even 123))])
+ ))
diff --git a/stdlib/source/documentation/lux/meta/type/resource.lux b/stdlib/source/documentation/lux/meta/type/resource.lux
index 5003b7896..ed1f271f3 100644
--- a/stdlib/source/documentation/lux/meta/type/resource.lux
+++ b/stdlib/source/documentation/lux/meta/type/resource.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except and)
+ [lux (.except)
["$" documentation]
[data
["[0]" text (.only \n)
@@ -8,89 +8,90 @@
[\\library
["[0]" /]])
-(`` (.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.monad)
- ($.definition /.index_cannot_be_repeated)
- ($.definition /.amount_cannot_be_zero)
-
- ($.definition (/.Procedure monad input output value)
- (format "A computation that takes a sequence of resource access rights as inputs and yields a different sequence as outputs."
- \n "A procedure yields a result value."
- \n "A procedure can make use of monadic effects."))
-
- ($.definition (/.Linear monad value)
- (format "A procedure that is constant with regards to resource access rights."
- \n "This means no additional resources will be available after the computation is over."
- \n "This also means no previously available resources will have been consumed."))
-
- ($.definition (/.Affine monad permissions value)
- "A procedure which expands the number of available resources.")
-
- ($.definition (/.Relevant monad permissions value)
- "A procedure which reduces the number of available resources.")
-
- ($.definition /.run!
- ""
- [(run! monad procedure)])
-
- ($.definition /.lifted
- ""
- [(lifted monad procedure)])
-
- ($.definition /.Ordered
- "The mode of keys which CANNOT be swapped, and for whom order of release/consumption matters.")
-
- ($.definition /.Commutative
- "The mode of keys which CAN be swapped, and for whom order of release/consumption DOES NOT matters.")
-
- ($.definition (/.Key mode key)
- (format "The access right for a resource."
- \n "Without the key for a resource existing somewhere among the available ambient rights, one cannot use a resource."))
-
- ($.definition (/.Res key value)
- (format "A resource locked by a key."
- \n "The 'key' represents the right to access/consume a resource."))
-
- (,, (with_template [<name>]
- [($.definition <name>
- "Makes a value into a resource and adds the key/access-right to it to the ambient keyring for future use.")]
-
- [/.ordered]
- [/.commutative]
- ))
-
- ($.definition /.read
- "Access the value of a resource, so long as its key is available."
- [(read monad resource)])
-
- ($.definition /.exchange
- (format "A function that can exchange the keys for resource, so long as they are commutative."
- \n "This keys will be placed at the front of the keyring in the order they are specified."
- \n "The specific keys must be specified based of their index into the current keyring.")
- [(do (monad !)
- [res|left (commutative ! pre)
- res|right (commutative ! post)
- _ ((exchange [1 0]) !)
- left (read ! res|left)
- right (read ! res|right)]
- (in (format left right)))])
-
- (,, (with_template [<name>]
- [($.definition <name>
- "Group/un-group keys in the keyring into/out-of tuples."
- [(do (monad !)
- [res|left (commutative ! pre)
- res|right (commutative ! post)
- _ ((group 2) !)
- _ ((un_group 2) !)
- right (read ! res|right)
- left (read ! res|left)]
- (in (format left right)))])]
-
- [/.group]
- [/.un_group]
- ))]
- [])))
+(`` (def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.monad)
+ ($.definition /.index_cannot_be_repeated)
+ ($.definition /.amount_cannot_be_zero)
+
+ ($.definition (/.Procedure monad input output value)
+ (format "A computation that takes a sequence of resource access rights as inputs and yields a different sequence as outputs."
+ \n "A procedure yields a result value."
+ \n "A procedure can make use of monadic effects."))
+
+ ($.definition (/.Linear monad value)
+ (format "A procedure that is constant with regards to resource access rights."
+ \n "This means no additional resources will be available after the computation is over."
+ \n "This also means no previously available resources will have been consumed."))
+
+ ($.definition (/.Affine monad permissions value)
+ "A procedure which expands the number of available resources.")
+
+ ($.definition (/.Relevant monad permissions value)
+ "A procedure which reduces the number of available resources.")
+
+ ($.definition /.run!
+ ""
+ [(run! monad procedure)])
+
+ ($.definition /.lifted
+ ""
+ [(lifted monad procedure)])
+
+ ($.definition /.Ordered
+ "The mode of keys which CANNOT be swapped, and for whom order of release/consumption matters.")
+
+ ($.definition /.Commutative
+ "The mode of keys which CAN be swapped, and for whom order of release/consumption DOES NOT matters.")
+
+ ($.definition (/.Key mode key)
+ (format "The access right for a resource."
+ \n "Without the key for a resource existing somewhere among the available ambient rights, one cannot use a resource."))
+
+ ($.definition (/.Res key value)
+ (format "A resource locked by a key."
+ \n "The 'key' represents the right to access/consume a resource."))
+
+ (,, (with_template [<name>]
+ [($.definition <name>
+ "Makes a value into a resource and adds the key/access-right to it to the ambient keyring for future use.")]
+
+ [/.ordered]
+ [/.commutative]
+ ))
+
+ ($.definition /.read
+ "Access the value of a resource, so long as its key is available."
+ [(read monad resource)])
+
+ ($.definition /.exchange
+ (format "A function that can exchange the keys for resource, so long as they are commutative."
+ \n "This keys will be placed at the front of the keyring in the order they are specified."
+ \n "The specific keys must be specified based of their index into the current keyring.")
+ [(do (monad !)
+ [res|left (commutative ! pre)
+ res|right (commutative ! post)
+ _ ((exchange [1 0]) !)
+ left (read ! res|left)
+ right (read ! res|right)]
+ (in (format left right)))])
+
+ (,, (with_template [<name>]
+ [($.definition <name>
+ "Group/un-group keys in the keyring into/out-of tuples."
+ [(do (monad !)
+ [res|left (commutative ! pre)
+ res|right (commutative ! post)
+ _ ((group 2) !)
+ _ ((un_group 2) !)
+ right (read ! res|right)
+ left (read ! res|left)]
+ (in (format left right)))])]
+
+ [/.group]
+ [/.un_group]
+ ))
+ )))
diff --git a/stdlib/source/documentation/lux/meta/type/unit.lux b/stdlib/source/documentation/lux/meta/type/unit.lux
index 5ad54ced9..606184c7a 100644
--- a/stdlib/source/documentation/lux/meta/type/unit.lux
+++ b/stdlib/source/documentation/lux/meta/type/unit.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except and)
+ [lux (.except)
["$" documentation]
[data
["[0]" text (.only \n)
@@ -14,77 +14,78 @@
[\\library
["[0]" /]])
-(`` (.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Gram)
- ($.definition /.Meter)
- ($.definition /.Litre)
- ($.definition /.Second)
- ... ($.definition /.pure)
- ($.definition /.number)
- ($.definition /.equivalence)
- ($.definition /.order)
- ($.definition /.enum)
- ... ($.definition /.Kilo)
- ... ($.definition /.Mega)
- ... ($.definition /.Giga)
- ... ($.definition /.Milli)
- ... ($.definition /.Micro)
- ... ($.definition /.Nano)
- ($.definition /.+)
- ($.definition /.-)
- ($.definition /.*)
- ($.definition /./)
+(`` (def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition (/.Measure unit)
- "A quantity with an associated unit of measurement.")
+ ($.definition /.Gram)
+ ($.definition /.Meter)
+ ($.definition /.Litre)
+ ($.definition /.Second)
+ ... ($.definition /.pure)
+ ($.definition /.number)
+ ($.definition /.equivalence)
+ ($.definition /.order)
+ ($.definition /.enum)
+ ... ($.definition /.Kilo)
+ ... ($.definition /.Mega)
+ ... ($.definition /.Giga)
+ ... ($.definition /.Milli)
+ ... ($.definition /.Micro)
+ ... ($.definition /.Nano)
+ ($.definition /.+)
+ ($.definition /.-)
+ ($.definition /.*)
+ ($.definition /./)
- ($.definition (/.Unit unit)
- "A unit of measurement, to qualify numbers with.")
+ ($.definition (/.Measure unit)
+ "A quantity with an associated unit of measurement.")
- ... ($.definition (/.Scale scale)
- ... "A scale of magnitude.")
+ ($.definition (/.Unit unit)
+ "A unit of measurement, to qualify numbers with.")
- ... ($.definition /.Pure
- ... "A pure, unit-less measure.")
+ ... ($.definition (/.Scale scale)
+ ... "A scale of magnitude.")
- ($.definition /.unit
- (format "Define a unit of measurement."
- \n "Both the name of the type, and the name of the Unit implementation must be specified.")
- [(def feet (unit []))])
+ ... ($.definition /.Pure
+ ... "A pure, unit-less measure.")
- ... ($.definition /.scale
- ... "Define a scale of magnitude."
- ... [(def bajillion (scale [1 1,234,567,890]))])
+ ($.definition /.unit
+ (format "Define a unit of measurement."
+ \n "Both the name of the type, and the name of the Unit implementation must be specified.")
+ [(def feet (unit []))])
- ... ($.definition /.re_scaled
- ... ""
- ... [(re_scaled from to measure)])
+ ... ($.definition /.scale
+ ... "Define a scale of magnitude."
+ ... [(def bajillion (scale [1 1,234,567,890]))])
- ... (,, (with_template [<type> <scale>]
- ... [(`` ($.definition <scale>
- ... (let [numerator (the [/.ratio ratio.#numerator] <scale>)
- ... denominator (the [/.ratio ratio.#denominator] <scale>)]
- ... (format "The '" (,, (template.text [<scale>])) "' scale, from " (%.nat numerator) " to " (%.nat denominator) "."))))]
+ ... ($.definition /.re_scaled
+ ... ""
+ ... [(re_scaled from to measure)])
- ... [/.Kilo /.kilo]
- ... [/.Mega /.mega]
- ... [/.Giga /.giga]
+ ... (,, (with_template [<type> <scale>]
+ ... [(`` ($.definition <scale>
+ ... (let [numerator (the [/.ratio ratio.#numerator] <scale>)
+ ... denominator (the [/.ratio ratio.#denominator] <scale>)]
+ ... (format "The '" (,, (template.text [<scale>])) "' scale, from " (%.nat numerator) " to " (%.nat denominator) "."))))]
- ... [/.Milli /.milli]
- ... [/.Micro /.micro]
- ... [/.Nano /.nano]
- ... ))
+ ... [/.Kilo /.kilo]
+ ... [/.Mega /.mega]
+ ... [/.Giga /.giga]
- (,, (with_template [<unit>]
- [(`` ($.definition <unit>
- (format "The '" (,, (template.text [<unit>])) "' unit of meaurement.")))]
+ ... [/.Milli /.milli]
+ ... [/.Micro /.micro]
+ ... [/.Nano /.nano]
+ ... ))
- [/.gram]
- [/.meter]
- [/.litre]
- [/.second]
- ))]
- [])))
+ (,, (with_template [<unit>]
+ [(`` ($.definition <unit>
+ (format "The '" (,, (template.text [<unit>])) "' unit of meaurement.")))]
+
+ [/.gram]
+ [/.meter]
+ [/.litre]
+ [/.second]
+ ))
+ )))
diff --git a/stdlib/source/documentation/lux/meta/type/variance.lux b/stdlib/source/documentation/lux/meta/type/variance.lux
index fa6c3e36f..5dcc89f9d 100644
--- a/stdlib/source/documentation/lux/meta/type/variance.lux
+++ b/stdlib/source/documentation/lux/meta/type/variance.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except and)
+ [lux (.except)
["$" documentation]
[data
["[0]" text (.only \n)
@@ -11,16 +11,17 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition (/.Co it)
- "A constraint for covariant types.")
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition (/.Contra it)
- "A constraint for contravariant types.")
+ ($.definition (/.Co it)
+ "A constraint for covariant types.")
- ($.definition (/.In it)
- "A constraint for invariant types.")]
- []))
+ ($.definition (/.Contra it)
+ "A constraint for contravariant types.")
+
+ ($.definition (/.In it)
+ "A constraint for invariant types.")
+ ))