aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/documentation
diff options
context:
space:
mode:
authorEduardo Julian2021-08-19 04:59:06 -0400
committerEduardo Julian2021-08-19 04:59:06 -0400
commitd772fe99d5d4990c6774481fb64d12280cdb6aae (patch)
tree209a2ce3b8e896be15db40bc58db830a5304b4f9 /stdlib/source/documentation
parente00ba096c8837abe85d366e0c1293c09dbe84d81 (diff)
Enabled compile-time code evaluation (i.e. "eval" function).
Diffstat (limited to 'stdlib/source/documentation')
-rw-r--r--stdlib/source/documentation/lux.lux25
-rw-r--r--stdlib/source/documentation/lux/abstract/monad.lux6
-rw-r--r--stdlib/source/documentation/lux/control/concurrency/frp.lux6
-rw-r--r--stdlib/source/documentation/lux/control/function.lux6
-rw-r--r--stdlib/source/documentation/lux/control/parser.lux26
-rw-r--r--stdlib/source/documentation/lux/control/parser/json.lux94
-rw-r--r--stdlib/source/documentation/lux/control/parser/synthesis.lux84
-rw-r--r--stdlib/source/documentation/lux/control/parser/text.lux221
-rw-r--r--stdlib/source/documentation/lux/control/parser/tree.lux72
-rw-r--r--stdlib/source/documentation/lux/control/parser/type.lux142
-rw-r--r--stdlib/source/documentation/lux/control/parser/xml.lux60
-rw-r--r--stdlib/source/documentation/lux/data.lux40
-rw-r--r--stdlib/source/documentation/lux/data/binary.lux91
-rw-r--r--stdlib/source/documentation/lux/data/bit.lux31
-rw-r--r--stdlib/source/documentation/lux/data/collection.lux40
-rw-r--r--stdlib/source/documentation/lux/data/collection/array.lux124
-rw-r--r--stdlib/source/documentation/lux/data/collection/bits.lux86
-rw-r--r--stdlib/source/documentation/lux/data/collection/dictionary.lux107
-rw-r--r--stdlib/source/documentation/lux/data/collection/dictionary/ordered.lux84
-rw-r--r--stdlib/source/documentation/lux/data/collection/dictionary/plist.lux58
-rw-r--r--stdlib/source/documentation/lux/data/collection/list.lux239
-rw-r--r--stdlib/source/documentation/lux/data/collection/queue.lux62
-rw-r--r--stdlib/source/documentation/lux/data/collection/queue/priority.lux41
-rw-r--r--stdlib/source/documentation/lux/data/collection/row.lux86
-rw-r--r--stdlib/source/documentation/lux/data/collection/sequence.lux98
-rw-r--r--stdlib/source/documentation/lux/data/color.lux126
-rw-r--r--stdlib/source/documentation/lux/data/color/named.lux319
27 files changed, 2349 insertions, 25 deletions
diff --git a/stdlib/source/documentation/lux.lux b/stdlib/source/documentation/lux.lux
index 1f30de85c..987d9cce5 100644
--- a/stdlib/source/documentation/lux.lux
+++ b/stdlib/source/documentation/lux.lux
@@ -10,7 +10,27 @@
["." /]]
["." / #_
["#." abstract]
- ["#." control]])
+ ["#." control]
+ ["#." data]
+ ... ["#." debug]
+ ... ["#." documentation]
+ ... ["#." locale]
+ ... ["#." macro
+ ... ["#/." code]]
+ ... ["#." math]
+ ... ["#." meta]
+ ... ["#." program]
+ ... ["#." target]
+ ... ["#." test]
+ ... ["#." time]
+ ... ... ["#." tool] ... TODO: Update & expand tests for this
+ ... ["#." type]
+ ... ["#." world]
+ ... ["#." ffi]
+ ... ["#." extension]
+ ... ["#." target #_
+ ... <target>]
+ ])
(documentation: /.:of
"Generates the type corresponding to a given expression."
@@ -28,7 +48,8 @@
""
[..:of]
[/abstract.documentation
- /control.documentation]))
+ /control.documentation
+ /data.documentation]))
(program: inputs
(io.io (debug.log! ($.documentation ..documentation))))
diff --git a/stdlib/source/documentation/lux/abstract/monad.lux b/stdlib/source/documentation/lux/abstract/monad.lux
index 2d55ff0c5..07318bce9 100644
--- a/stdlib/source/documentation/lux/abstract/monad.lux
+++ b/stdlib/source/documentation/lux/abstract/monad.lux
@@ -25,9 +25,9 @@
"Apply a function with monadic effects to a monadic value and yield a new monadic value."
[(then monad function)])
-(documentation: /.seq
+(documentation: /.all
"Run all the monadic values in the list and produce a list of the base values."
- [(seq monad)])
+ [(all monad)])
(documentation: /.map
"Apply a monadic function to all values in a list."
@@ -48,7 +48,7 @@
[..Monad
..do
..then
- ..seq
+ ..all
..map
..only
..fold]
diff --git a/stdlib/source/documentation/lux/control/concurrency/frp.lux b/stdlib/source/documentation/lux/control/concurrency/frp.lux
index 2500b119d..728e93be5 100644
--- a/stdlib/source/documentation/lux/control/concurrency/frp.lux
+++ b/stdlib/source/documentation/lux/control/concurrency/frp.lux
@@ -32,9 +32,9 @@
"A one-element channel containing the output from an async."
[(of_async async)])
-(documentation: /.fold
+(documentation: /.aggregate
"Asynchronous fold over channels."
- [(fold f init channel)])
+ [(aggregate f init channel)])
(documentation: /.sequential
"Transforms the given list into a channel with the same elements."
@@ -50,7 +50,7 @@
..Subscriber
..only
..of_async
- ..fold
+ ..aggregate
..sequential
($.default /.channel_is_already_closed)
($.default /.functor)
diff --git a/stdlib/source/documentation/lux/control/function.lux b/stdlib/source/documentation/lux/control/function.lux
index 88556dda7..62f7b7374 100644
--- a/stdlib/source/documentation/lux/control/function.lux
+++ b/stdlib/source/documentation/lux/control/function.lux
@@ -36,9 +36,9 @@
[(= ((flipped f) "foo" "bar")
(f "bar" "foo"))])
-(documentation: /.apply
+(documentation: /.on
"Simple 1-argument function application."
- [(apply input function)])
+ [(on input function)])
(.def: .public documentation
(.List $.Module)
@@ -48,7 +48,7 @@
..composite
..constant
..flipped
- ..apply
+ ..on
($.default /.monoid)]
[/contract.documentation
/memo.documentation
diff --git a/stdlib/source/documentation/lux/control/parser.lux b/stdlib/source/documentation/lux/control/parser.lux
index 081c5a792..7c6691d60 100644
--- a/stdlib/source/documentation/lux/control/parser.lux
+++ b/stdlib/source/documentation/lux/control/parser.lux
@@ -15,13 +15,12 @@
["#." cli]
["#." code]
["#." environment]
- ... ["#." json]
- ... ["#." synthesis]
- ... ["#." text]
- ... ["#." tree]
- ... ["#." type]
- ... ["#." xml]
- ])
+ ["#." json]
+ ["#." synthesis]
+ ["#." text]
+ ["#." tree]
+ ["#." type]
+ ["#." xml]])
(documentation: /.Parser
"A generic parser.")
@@ -171,10 +170,9 @@
/cli.documentation
/code.documentation
/environment.documentation
- ... /json.documentation
- ... /synthesis.documentation
- ... /text.documentation
- ... /tree.documentation
- ... /type.documentation
- ... /xml.documentation
- ]))
+ /json.documentation
+ /synthesis.documentation
+ /text.documentation
+ /tree.documentation
+ /type.documentation
+ /xml.documentation]))
diff --git a/stdlib/source/documentation/lux/control/parser/json.lux b/stdlib/source/documentation/lux/control/parser/json.lux
new file mode 100644
index 000000000..8dfa6a8d3
--- /dev/null
+++ b/stdlib/source/documentation/lux/control/parser/json.lux
@@ -0,0 +1,94 @@
+(.module:
+ [library
+ [lux #*
+ ["$" documentation (#+ documentation:)]
+ [data
+ [text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ ["." template]]]]
+ [\\library
+ ["." /]])
+
+(documentation: /.Parser
+ "A JSON parser.")
+
+(documentation: /.result
+ (format "Executes the parser against a JSON object."
+ \n "Verifies that all of the JSON was consumed by the parser.")
+ [(result parser json)])
+
+(documentation: /.any
+ "Just returns the JSON input without applying any logic.")
+
+(template [<name>]
+ [(`` (documentation: <name>
+ (format "Reads a JSON value as " (~~ (template.text [<name>])) ".")))]
+
+ [/.null]
+ [/.boolean]
+ [/.number]
+ [/.string]
+ )
+
+(template [<test> <check> <read>]
+ [(`` (documentation: <test>
+ (format "Asks whether a JSON value is a " (~~ (template.text [<read>])) ".")
+ [(<test> test)]))
+ (`` (documentation: <check>
+ (format "Ensures a JSON value is a " (~~ (template.text [<read>])) ".")
+ [(<check> test)]))]
+
+ [/.boolean? /.boolean! ..boolean]
+ [/.number? /.number! ..number]
+ [/.string? /.string! ..string]
+ )
+
+(documentation: /.nullable
+ "Enhances parser by adding NULL-handling."
+ [(nullable parser)])
+
+(documentation: /.array
+ "Parses the contents of a JSON array."
+ [(array parser)])
+
+(documentation: /.object
+ (format "Parses the contents of a JSON object."
+ \n "Use this with the 'field' combinator.")
+ [(object parser)])
+
+(documentation: /.field
+ (format "Parses a field inside a JSON object."
+ \n "Use this inside the 'object' combinator.")
+ [(field field_name parser)])
+
+(documentation: /.dictionary
+ "Parses a dictionary-like JSON object.")
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..Parser
+ ..result
+ ..any
+
+ ..null
+ ..boolean
+ ..number
+ ..string
+
+ ..boolean? ..boolean!
+ ..number? ..number!
+ ..string? ..string!
+
+ ..nullable
+ ..array
+ ..object
+ ..field
+ ..dictionary
+ ($.default /.unconsumed_input)
+ ($.default /.empty_input)
+ ($.default /.unexpected_value)
+ ($.default /.value_mismatch)]
+ []))
diff --git a/stdlib/source/documentation/lux/control/parser/synthesis.lux b/stdlib/source/documentation/lux/control/parser/synthesis.lux
new file mode 100644
index 000000000..82b3224ea
--- /dev/null
+++ b/stdlib/source/documentation/lux/control/parser/synthesis.lux
@@ -0,0 +1,84 @@
+(.module:
+ [library
+ [lux (#- i64 local function loop)
+ ["$" documentation (#+ documentation:)]
+ [data
+ [text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ ["." template]]]]
+ [\\library
+ ["." /]])
+
+(documentation: /.Parser
+ "A parser for the Lux compiler's synthesis nodes using during optimization.")
+
+(documentation: /.result
+ (format "Executes the parser against the inputs."
+ \n "Ensures all inputs are consumed by the parser.")
+ [(result parser input)])
+
+(documentation: /.any
+ "Yields a synthesis node without subjecting it to any analysis.")
+
+(documentation: /.end!
+ "Ensures there are no more inputs.")
+
+(documentation: /.end?
+ "Checks whether there are no more inputs.")
+
+(template [<query> <assertion>]
+ [(`` (documentation: <query>
+ (format "Queries for a " (~~ (template.text [<query>])) " synthesis node.")))
+ (`` (documentation: <assertion>
+ (format "Checks for a specific " (~~ (template.text [<query>])) " synthesis node.")
+ [(<assertion> expected)]))]
+
+ [/.bit /.bit!]
+ [/.i64 /.i64!]
+ [/.f64 /.f64!]
+ [/.text /.text!]
+ [/.local /.local!]
+ [/.foreign /.foreign!]
+ [/.constant /.constant!]
+ )
+
+(documentation: /.tuple
+ "Parses the contents of a tuple."
+ [(tuple parser)])
+
+(documentation: /.function
+ "Parses the body of a function with the 'expected' arity."
+ [(function expected parser)])
+
+(documentation: /.loop
+ "Parses the initial values and the body of a loop."
+ [(loop init_parsers iteration_parser)])
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..Parser
+ ..result
+ ..any
+ ..end!
+ ..end?
+
+ ..bit ..bit!
+ ..i64 ..i64!
+ ..f64 ..f64!
+ ..text ..text!
+ ..local ..local!
+ ..foreign ..foreign!
+ ..constant ..constant!
+
+ ..tuple
+ ..function
+ ..loop
+ ($.default /.cannot_parse)
+ ($.default /.unconsumed_input)
+ ($.default /.expected_empty_input)
+ ($.default /.wrong_arity)
+ ($.default /.empty_input)]
+ []))
diff --git a/stdlib/source/documentation/lux/control/parser/text.lux b/stdlib/source/documentation/lux/control/parser/text.lux
new file mode 100644
index 000000000..52c1c6b07
--- /dev/null
+++ b/stdlib/source/documentation/lux/control/parser/text.lux
@@ -0,0 +1,221 @@
+(.module:
+ [library
+ [lux (#- and not local)
+ ["$" documentation (#+ documentation:)]
+ [data
+ [text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ ["." template]]]]
+ [\\library
+ ["." /]])
+
+(documentation: /.Offset
+ "An offset into a block of text.")
+
+(documentation: /.Parser
+ "A parser for text.")
+
+(documentation: /.Slice
+ "A slice of a block of text.")
+
+(documentation: /.result
+ (format "Executes a parser against a block of text."
+ \n "Verifies that the entire input has been processed.")
+ [(result parser input)])
+
+(documentation: /.offset
+ "Yields the current offset into the input.")
+
+(documentation: /.any
+ "Yields the next character without applying any logic.")
+
+(documentation: /.any!
+ "Yields the next character (as a slice) without applying any logic.")
+
+(template [<name> <caveat>]
+ [(`` (documentation: <name>
+ (format "Produce a character" (~~ (template.text [<caveat>])) " if the parser fails.")
+ [(<name> parser)]))]
+
+ [/.not ""]
+ [/.not! " (as a slice)"]
+ )
+
+(documentation: /.this
+ "Checks that a specific text shows up in the input."
+ [(this reference)])
+
+(documentation: /.end!
+ "Ensure the parser's input is empty.")
+
+(documentation: /.next
+ "Yields the next character (without consuming it from the input).")
+
+(documentation: /.remaining
+ "Get all of the remaining input (without consuming it).")
+
+(documentation: /.range
+ "Only yields characters within a range."
+ [(range bottom top)])
+
+(template [<name> <desc>]
+ [(documentation: <name>
+ (format "Only yields " <desc> " characters."))]
+
+ [/.upper "uppercase"]
+ [/.lower "lowercase"]
+ [/.decimal "decimal"]
+ [/.octal "octal"]
+ )
+
+(documentation: /.alpha
+ "Yields alphabetic characters.")
+
+(documentation: /.alpha_num
+ "Yields alphanumeric characters.")
+
+(documentation: /.hexadecimal
+ "Yields hexadecimal digits.")
+
+(template [<name> <description_modifier>]
+ [(documentation: <name>
+ (format "Yields characters that are" <description_modifier> " part of a piece of text.")
+ [(<name> options)])]
+
+ [/.one_of ""]
+ [/.none_of " not"]
+ )
+
+(template [<name> <description_modifier>]
+ [(documentation: <name>
+ (format "Yields characters (as a slice) that are" <description_modifier> " part of a piece of text.")
+ [(<name> options)])]
+
+ [/.one_of! ""]
+ [/.none_of! " not"]
+ )
+
+(documentation: /.satisfies
+ "Yields characters that satisfy a predicate."
+ [(satisfies parser)])
+
+(documentation: /.space
+ "Yields white-space.")
+
+(documentation: /.and
+ "Yields the outputs of both parsers composed together."
+ [(and left right)])
+
+(documentation: /.and!
+ "Yields the outputs of both parsers composed together (as a slice)."
+ [(and! left right)])
+
+(template [<text> <slice>]
+ [(`` (documentation: <text>
+ (format "Yields " (~~ (template.text [<name>])) " characters as a single continuous text.")
+ [(<text> parser)]))
+ (`` (documentation: <slice>
+ (format "Yields " (~~ (template.text [<name>])) " characters as a single continuous text (as a slice).")
+ [(<slice> parser)]))]
+
+ [/.some /.some!]
+ [/.many /.many!]
+ )
+
+(template [<text> <slice> <doc_modifier>]
+ [(`` (documentation: <text>
+ (format "Yields " <doc_modifier> " N characters.")
+ [(<text> amount parser)]))
+ (`` (documentation: <slice>
+ (format "Yields " <doc_modifier> " N characters (as a slice).")
+ [(<slice> amount parser)]))]
+
+ [/.exactly /.exactly! "exactly"]
+ [/.at_most /.at_most! "at most"]
+ [/.at_least /.at_least! "at least"]
+ )
+
+(documentation: /.between
+ ""
+ [(between minimum additional parser)])
+
+(documentation: /.between!
+ ""
+ [(between! minimum additional parser)])
+
+(documentation: /.enclosed
+ ""
+ [(enclosed [start end] parser)])
+
+(documentation: /.local
+ "Applies a parser against the given input."
+ [(local local_input parser)])
+
+(documentation: /.slice
+ "Converts a slice to a block of text."
+ [(slice parser)])
+
+(documentation: /.then
+ "Embeds a text parser into an arbitrary parser that yields text."
+ [(then structured text)])
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..Offset
+ ..Parser
+ ..Slice
+ ..result
+ ..offset
+
+ ..any ..any!
+ ..not ..not!
+
+ ..this
+ ..end!
+ ..next
+ ..remaining
+ ..range
+
+ ..upper
+ ..lower
+ ..decimal
+ ..octal
+
+ ..alpha
+ ..alpha_num
+ ..hexadecimal
+
+ ..one_of ..one_of!
+ ..none_of ..none_of!
+
+ ..satisfies
+ ..space
+ ..and ..and!
+
+ ..some ..some!
+ ..many ..many!
+
+
+ ..exactly ..exactly!
+ ..at_most ..at_most!
+ ..at_least ..at_least!
+
+ ..between
+ ..between!
+ ..enclosed
+ ..local
+ ..slice
+ ..then
+
+ ($.default /.unconsumed_input)
+ ($.default /.expected_to_fail)
+ ($.default /.cannot_parse)
+ ($.default /.cannot_slice)
+ ($.default /.cannot_match)
+ ($.default /.character_should_be)
+ ($.default /.character_should_not_be)
+ ($.default /.character_does_not_satisfy_predicate)]
+ []))
diff --git a/stdlib/source/documentation/lux/control/parser/tree.lux b/stdlib/source/documentation/lux/control/parser/tree.lux
new file mode 100644
index 000000000..3c5cf1bf7
--- /dev/null
+++ b/stdlib/source/documentation/lux/control/parser/tree.lux
@@ -0,0 +1,72 @@
+(.module:
+ [library
+ [lux #*
+ ["$" documentation (#+ documentation:)]
+ [data
+ [text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ ["." template]]]]
+ [\\library
+ ["." /]])
+
+(documentation: /.Parser
+ "A parser of arbitrary trees.")
+
+(documentation: /.result'
+ "Applies the parser against a tree zipper."
+ [(result' parser zipper)])
+
+(documentation: /.result
+ "Applies the parser against a tree."
+ [(result parser tree)])
+
+(documentation: /.value
+ "Yields the value inside the current tree node.")
+
+(template [<name> <doc>]
+ [(documentation: <name>
+ <doc>)]
+
+ [/.down "Move down."]
+ [/.up "Move up."]
+
+ [/.right "Move to the right."]
+ [/.rightmost "Move to the rightmost node."]
+
+ [/.left "Move to the left."]
+ [/.leftmost "Move to the leftmost node."]
+
+ [/.next "Move to the next node."]
+ [/.end "Move to the last node."]
+
+ [/.previous "Move to the previous node."]
+ [/.start "Move to the root node."]
+ )
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..Parser
+ ..result'
+ ..result
+ ..value
+
+ ..down
+ ..up
+
+ ..right
+ ..rightmost
+
+ ..left
+ ..leftmost
+
+ ..next
+ ..end
+
+ ..previous
+ ..start
+
+ ($.default /.cannot_move_further)]
+ []))
diff --git a/stdlib/source/documentation/lux/control/parser/type.lux b/stdlib/source/documentation/lux/control/parser/type.lux
new file mode 100644
index 000000000..0d1785b06
--- /dev/null
+++ b/stdlib/source/documentation/lux/control/parser/type.lux
@@ -0,0 +1,142 @@
+(.module:
+ [library
+ [lux (#- local function)
+ ["$" documentation (#+ documentation:)]
+ [data
+ [text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ ["." template]]]]
+ [\\library
+ ["." /]])
+
+(documentation: /.Env
+ "An environment for type parsing.")
+
+(documentation: /.Parser
+ "A parser of Lux types.")
+
+(documentation: /.fresh
+ "An empty parsing environment.")
+
+(documentation: /.result
+ (format "Applies a parser against a type."
+ \n "Verifies that the parser fully consumes the type's information.")
+ [(result poly type)])
+
+(documentation: /.env
+ "Yields the current parsing environment.")
+
+(documentation: /.next
+ "Inspect a type in the input stream without consuming it.")
+
+(documentation: /.any
+ "Yields a type, without examination.")
+
+(documentation: /.local
+ "Apply a parser to the given inputs."
+ [(local types poly)])
+
+(documentation: /.with_extension
+ ""
+ [(with_extension type poly)])
+
+(template [<name>]
+ [(`` (documentation: <name>
+ (format "Parses the contents of a " (~~ (template.text [<name>])) " type.")
+ [(<name> poly)]))]
+
+ [/.variant]
+ [/.tuple]
+ )
+
+(documentation: /.polymorphic
+ ""
+ [(polymorphic poly)])
+
+(documentation: /.function
+ "Parses a function's inputs and output."
+ [(function in_poly out_poly)])
+
+(documentation: /.applied
+ "Parses a type application."
+ [(applied poly)])
+
+(template [<name> <doc>]
+ [(documentation: <name>
+ <doc>
+ [(<name> expected)])]
+
+ [/.exactly "Parses a type exactly."]
+ [/.sub "Parses a sub type."]
+ [/.super "Parses a super type."]
+ )
+
+(documentation: /.adjusted_idx
+ ""
+ [(adjusted_idx env idx)])
+
+(documentation: /.parameter!
+ ""
+ [(parameter! id)])
+
+(documentation: /.existential
+ "Yields an existential type.")
+
+(documentation: /.named
+ "Yields a named type.")
+
+(documentation: /.recursive
+ ""
+ [(recursive poly)])
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ (format "Parsing of Lux types."
+ \n "Used mostly for polytypic programming.")
+ [..Env
+ ..Parser
+ ..fresh
+ ..result
+ ..env
+ ..next
+ ..any
+ ..local
+ ..with_extension
+
+ ..variant
+ ..tuple
+
+ ..polymorphic
+ ..function
+ ..applied
+
+ ..exactly
+ ..sub
+ ..super
+
+ ..adjusted_idx
+ ..parameter!
+ ..existential
+ ..named
+ ..recursive
+
+ ($.default /.not_existential)
+ ($.default /.not_recursive)
+ ($.default /.not_named)
+ ($.default /.not_parameter)
+ ($.default /.unknown_parameter)
+ ($.default /.not_function)
+ ($.default /.not_application)
+ ($.default /.not_polymorphic)
+ ($.default /.not_variant)
+ ($.default /.not_tuple)
+ ($.default /.types_do_not_match)
+ ($.default /.wrong_parameter)
+ ($.default /.empty_input)
+ ($.default /.unconsumed_input)
+ ($.default /.parameter)
+ ($.default /.recursive_self)
+ ($.default /.recursive_call)]
+ []))
diff --git a/stdlib/source/documentation/lux/control/parser/xml.lux b/stdlib/source/documentation/lux/control/parser/xml.lux
new file mode 100644
index 000000000..71390acdb
--- /dev/null
+++ b/stdlib/source/documentation/lux/control/parser/xml.lux
@@ -0,0 +1,60 @@
+(.module:
+ [library
+ [lux #*
+ ["$" documentation (#+ documentation:)]
+ [data
+ [text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ ["." template]]]]
+ [\\library
+ ["." /]])
+
+(documentation: /.Parser
+ "A parser of XML-encoded data.")
+
+(documentation: /.result
+ (format "Applies a parser against a stream of XML documents."
+ \n "Verifies that all of the inputs are consumed by the parser.")
+ [(result parser documents)])
+
+(documentation: /.text
+ "Yields text from a text node.")
+
+(documentation: /.tag
+ "Yields the tag from the next node.")
+
+(documentation: /.attribute
+ "Yields the value of an attribute in the current node."
+ [(attribute name)])
+
+(documentation: /.node
+ "Parses the contents of the next node if the tag matches."
+ [(node expected parser)])
+
+(documentation: /.any
+ "Yields the next node.")
+
+(documentation: /.somewhere
+ "Applies the parser somewhere among the remaining inputs; instead of demanding that the parser succeeds against the immediate inputs."
+ [(somewhere parser)])
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..Parser
+ ..result
+ ..text
+ ..tag
+ ..attribute
+ ..node
+ ..any
+ ..somewhere
+ ($.default /.empty_input)
+ ($.default /.unexpected_input)
+ ($.default /.wrong_tag)
+ ($.default /.unknown_attribute)
+ ($.default /.unconsumed_inputs)
+ ($.default /.nowhere)]
+ []))
diff --git a/stdlib/source/documentation/lux/data.lux b/stdlib/source/documentation/lux/data.lux
new file mode 100644
index 000000000..0939016a1
--- /dev/null
+++ b/stdlib/source/documentation/lux/data.lux
@@ -0,0 +1,40 @@
+(.module:
+ [library
+ [lux #*
+ ["$" documentation (#+ documentation:)]
+ [data
+ [text (#+ \n)
+ ["%" format (#+ format)]]
+ [collection
+ ["." list]]]]]
+ ["." / #_
+ ["#." binary]
+ ["#." bit]
+ ["#." collection]
+ ["#." color]
+ ... ["#." identity]
+ ... ["#." name]
+ ... ["#." product]
+ ... ["#." sum]
+ ... ["#." text]
+ ... ["#." format #_
+ ... ["#/." binary]
+ ... ["#/." json]
+ ... ["#/." tar]
+ ... ["#/." xml]]
+ ])
+
+(.def: .public documentation
+ (.List $.Module)
+ (list.together
+ (list /binary.documentation
+ /bit.documentation
+ /collection.documentation
+ /color.documentation
+ ... /identity.documentation
+ ... /name.documentation
+ ... /product.documentation
+ ... /sum.documentation
+ ... /text.documentation
+ ... /format.documentation
+ )))
diff --git a/stdlib/source/documentation/lux/data/binary.lux b/stdlib/source/documentation/lux/data/binary.lux
new file mode 100644
index 000000000..c740e6660
--- /dev/null
+++ b/stdlib/source/documentation/lux/data/binary.lux
@@ -0,0 +1,91 @@
+(.module:
+ [library
+ [lux #*
+ ["$" documentation (#+ documentation:)]
+ [data
+ [text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ ["." template]]]]
+ [\\library
+ ["." /]])
+
+(documentation: /.Binary
+ "A binary BLOB of data.")
+
+(documentation: /.empty
+ "A fresh/empty binary BLOB of the specified size."
+ [(empty size)])
+
+(documentation: /.aggregate
+ ""
+ [(aggregate f init binary)])
+
+(documentation: /.read/8!
+ "Read 1 byte (8 bits) at the given index."
+ [(read/8! index binary)])
+
+(documentation: /.read/16!
+ "Read 2 bytes (16 bits) at the given index."
+ [(read/16! index binary)])
+
+(documentation: /.read/32!
+ "Read 4 bytes (32 bits) at the given index."
+ [(read/32! index binary)])
+
+(documentation: /.read/64!
+ "Read 8 bytes (64 bits) at the given index."
+ [(read/64! index binary)])
+
+(documentation: /.write/8!
+ "Write 1 byte (8 bits) at the given index."
+ [(write/8! index value binary)])
+
+(documentation: /.write/16!
+ "Write 2 bytes (16 bits) at the given index."
+ [(write/16! index value binary)])
+
+(documentation: /.write/32!
+ "Write 4 bytes (32 bits) at the given index."
+ [(write/32! index value binary)])
+
+(documentation: /.write/64!
+ "Write 8 bytes (64 bits) at the given index."
+ [(write/64! index value binary)])
+
+(documentation: /.copy
+ "Mutates the target binary BLOB by copying bytes from the source BLOB to it."
+ [(copy bytes source_offset source target_offset target)])
+
+(documentation: /.slice
+ "Yields a subset of the binary BLOB, so long as the specified range is valid."
+ [(slice offset length binary)])
+
+(documentation: /.after
+ "Yields a binary BLOB with at most the specified number of bytes removed."
+ [(after bytes binary)])
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..Binary
+ ..empty
+ ..aggregate
+ ..read/8!
+ ..read/16!
+ ..read/32!
+ ..read/64!
+ ..write/8!
+ ..write/16!
+ ..write/32!
+ ..write/64!
+ ..copy
+ ..slice
+ ..after
+ ($.default /.index_out_of_bounds)
+ ($.default /.slice_out_of_bounds)
+ ($.default /.size)
+ ($.default /.equivalence)
+ ($.default /.monoid)]
+ []))
diff --git a/stdlib/source/documentation/lux/data/bit.lux b/stdlib/source/documentation/lux/data/bit.lux
new file mode 100644
index 000000000..e1379b85c
--- /dev/null
+++ b/stdlib/source/documentation/lux/data/bit.lux
@@ -0,0 +1,31 @@
+(.module:
+ [library
+ [lux #*
+ ["$" documentation (#+ documentation:)]
+ [data
+ [text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ ["." template]]]]
+ [\\library
+ ["." /]])
+
+(documentation: /.complement
+ (format "Generates the complement of a predicate."
+ \n "That is a predicate that returns the oposite of the original predicate."))
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..complement
+ ($.default /.no)
+ ($.default /.yes)
+ ($.default /.off)
+ ($.default /.on)
+ ($.default /.equivalence)
+ ($.default /.hash)
+ ($.default /.disjunction)
+ ($.default /.conjunction)
+ ($.default /.codec)]
+ []))
diff --git a/stdlib/source/documentation/lux/data/collection.lux b/stdlib/source/documentation/lux/data/collection.lux
new file mode 100644
index 000000000..e96f59465
--- /dev/null
+++ b/stdlib/source/documentation/lux/data/collection.lux
@@ -0,0 +1,40 @@
+(.module:
+ [library
+ [lux #*
+ ["$" documentation (#+ documentation:)]
+ [data
+ [text (#+ \n)
+ ["%" format (#+ format)]]
+ [collection
+ ["." list]]]]]
+ ["." / #_
+ ["#." array]
+ ["#." bits]
+ ["#." dictionary]
+ ["#." list]
+ ["#." queue]
+ ["#." row]
+ ["#." sequence]
+ ... ["#." stack]
+ ... ["#." set
+ ... ["#/." multi]
+ ... ["#/." ordered]]
+ ... ["#." tree
+ ... ["#/." finger]
+ ... ["#/." zipper]]
+ ])
+
+(.def: .public documentation
+ (.List $.Module)
+ (list.together
+ (list /array.documentation
+ /bits.documentation
+ /dictionary.documentation
+ /list.documentation
+ /queue.documentation
+ /row.documentation
+ /sequence.documentation
+ ... /stack.documentation
+ ... /set.documentation
+ ... /tree.documentation
+ )))
diff --git a/stdlib/source/documentation/lux/data/collection/array.lux b/stdlib/source/documentation/lux/data/collection/array.lux
new file mode 100644
index 000000000..3bf22b587
--- /dev/null
+++ b/stdlib/source/documentation/lux/data/collection/array.lux
@@ -0,0 +1,124 @@
+(.module:
+ [library
+ [lux (#- example list)
+ ["$" documentation (#+ documentation:)]
+ [control
+ ["<>" parser
+ ["<.>" code]]]
+ [data
+ ["." text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ [syntax (#+ syntax:)]
+ ["." code]
+ ["." template]]]]
+ [\\library
+ ["." /]])
+
+(documentation: /.Array
+ "Mutable arrays.")
+
+(documentation: /.empty
+ "An empty array of the specified size."
+ [(empty size)])
+
+(documentation: /.size
+ ""
+ [(size array)])
+
+(documentation: /.read!
+ ""
+ [(read! index array)])
+
+(documentation: /.write!
+ "Mutate the array by writing a value to the specified index."
+ [(write! index value array)])
+
+(documentation: /.delete!
+ "Mutate the array by deleting the value at the specified index."
+ [(delete! index array)])
+
+(documentation: /.contains?
+ ""
+ [(contains? index array)])
+
+(documentation: /.update!
+ "Mutate the array by updating the value at the specified index."
+ [(update! index transform array)])
+
+(documentation: /.upsert!
+ (format "Mutate the array by updating the value at the specified index."
+ \n "If there is no value, update and write the default value given.")
+ [(upsert! index default transform array)])
+
+(documentation: /.copy!
+ "Writes the contents of one array into the other."
+ [(copy! length src_start src_array dest_start dest_array)])
+
+(documentation: /.occupancy
+ "Finds out how many cells in an array are occupied."
+ [(occupancy array)])
+
+(documentation: /.vacancy
+ "Finds out how many cells in an array are vacant."
+ [(vacancy array)])
+
+(documentation: /.filter!
+ "Delete every item of the array that fails to satisfy the predicate."
+ [(filter! p xs)])
+
+(documentation: /.example
+ "Yields the first item in the array that satisfies the predicate."
+ [(example p xs)])
+
+(documentation: /.example+
+ "Just like 'example', but with access to the index of each value."
+ [(example+ p xs)])
+
+(documentation: /.clone
+ "Yields a shallow clone of the array."
+ [(clone xs)])
+
+(documentation: /.of_list
+ ""
+ [(of_list xs)])
+
+(documentation: /.list
+ "Yields a list with every non-empty item in the array."
+ [(list array)])
+
+(documentation: /.list'
+ "Like 'list', but uses the 'default' value when encountering an empty cell in the array."
+ [(list' default array)])
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..Array
+ ..empty
+ ..size
+ ..read!
+ ..write!
+ ..delete!
+ ..contains?
+ ..update!
+ ..upsert!
+ ..copy!
+ ..occupancy
+ ..vacancy
+ ..filter!
+ ..example
+ ..example+
+ ..clone
+ ..of_list
+ ..list
+ ..list'
+ ($.default /.type_name)
+ ($.default /.equivalence)
+ ($.default /.monoid)
+ ($.default /.functor)
+ ($.default /.fold)
+ ($.default /.every?)
+ ($.default /.any?)]
+ []))
diff --git a/stdlib/source/documentation/lux/data/collection/bits.lux b/stdlib/source/documentation/lux/data/collection/bits.lux
new file mode 100644
index 000000000..f5fe95dc3
--- /dev/null
+++ b/stdlib/source/documentation/lux/data/collection/bits.lux
@@ -0,0 +1,86 @@
+(.module:
+ [library
+ [lux (#- or and not)
+ ["$" documentation (#+ documentation:)]
+ [control
+ ["<>" parser
+ ["<.>" code]]]
+ [data
+ ["." text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ [syntax (#+ syntax:)]
+ ["." code]
+ ["." template]]]]
+ [\\library
+ ["." /]])
+
+(documentation: /.Bits
+ "A bit-map.")
+
+(documentation: /.size
+ "Measures the size of a bit-map by counting all the 1s in the bit-map."
+ [(size bits)])
+
+(documentation: /.capacity
+ ""
+ [(capacity bits)])
+
+(documentation: /.bit
+ ""
+ [(bit index bits)])
+
+(template [<name>]
+ [(documentation: <name>
+ ""
+ [(<name> index input)])]
+
+ [/.one]
+ [/.zero]
+ [/.flipped]
+ )
+
+(documentation: /.intersects?
+ ""
+ [(intersects? reference sample)])
+
+(documentation: /.not
+ ""
+ [(not input)])
+
+(template [<name>]
+ [(documentation: <name>
+ ""
+ [(<name> param subject)])]
+
+ [/.and]
+ [/.or]
+ [/.xor]
+ )
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..Bits
+ ..size
+ ..capacity
+ ..bit
+
+ ..one
+ ..zero
+ ..flipped
+
+ ..intersects?
+ ..not
+
+ ..and
+ ..or
+ ..xor
+
+ ($.default /.Chunk)
+ ($.default /.chunk_size)
+ ($.default /.empty)
+ ($.default /.empty?)
+ ($.default /.equivalence)]
+ []))
diff --git a/stdlib/source/documentation/lux/data/collection/dictionary.lux b/stdlib/source/documentation/lux/data/collection/dictionary.lux
new file mode 100644
index 000000000..95d2f998a
--- /dev/null
+++ b/stdlib/source/documentation/lux/data/collection/dictionary.lux
@@ -0,0 +1,107 @@
+(.module:
+ [library
+ [lux #*
+ ["$" documentation (#+ documentation:)]
+ [control
+ ["<>" parser
+ ["<.>" code]]]
+ [data
+ ["." text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ [syntax (#+ syntax:)]
+ ["." code]
+ ["." template]]]]
+ [\\library
+ ["." /]]
+ ["." / #_
+ ["#." ordered]
+ ["#." plist]])
+
+(documentation: /.Dictionary
+ "A dictionary implemented as a Hash-Array Mapped Trie (HAMT).")
+
+(documentation: /.empty
+ "An empty dictionary."
+ [(empty key_hash)])
+
+(documentation: /.has
+ ""
+ [(has key val dict)])
+
+(documentation: /.lacks
+ ""
+ [(lacks key dict)])
+
+(documentation: /.value
+ ""
+ [(value key dict)])
+
+(documentation: /.key?
+ ""
+ [(key? dict key)])
+
+(documentation: /.has'
+ "Only puts the KV-pair if the key is not already present."
+ [(has' key val dict)])
+
+(documentation: /.revised
+ "Transforms the value located at key (if available), using the given function."
+ [(revised key f dict)])
+
+(documentation: /.revised'
+ (format "Updates the value at the key; if it exists."
+ \n "Otherwise, puts a value by applying the function to a default.")
+ [(revised' key default f dict)])
+
+(documentation: /.of_list
+ ""
+ [(of_list key_hash kvs)])
+
+(documentation: /.merged
+ (format "Merges 2 dictionaries."
+ \n "If any collisions with keys occur, the values of dict2 will overwrite those of dict1.")
+ [(merged dict2 dict1)])
+
+(documentation: /.merged_with
+ (format "Merges 2 dictionaries."
+ \n "If any collisions with keys occur, a new value will be computed by applying 'f' to the values of dict2 and dict1.")
+ [(merged_with f dict2 dict1)])
+
+(documentation: /.re_bound
+ "If there is a value under 'from_key', remove 'from_key' and store the value under 'to_key'."
+ [(re_bound from_key to_key dict)])
+
+(documentation: /.sub
+ "A sub-dictionary, with only the specified keys."
+ [(sub keys dict)])
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..Dictionary
+ ..empty
+ ..has
+ ..lacks
+ ..value
+ ..key?
+ ..has'
+ ..revised
+ ..revised'
+ ..of_list
+ ..merged
+ ..merged_with
+ ..re_bound
+ ..sub
+ ($.default /.key_hash)
+ ($.default /.key_already_exists)
+ ($.default /.size)
+ ($.default /.empty?)
+ ($.default /.entries)
+ ($.default /.keys)
+ ($.default /.values)
+ ($.default /.equivalence)
+ ($.default /.functor)]
+ [/ordered.documentation
+ /plist.documentation]))
diff --git a/stdlib/source/documentation/lux/data/collection/dictionary/ordered.lux b/stdlib/source/documentation/lux/data/collection/dictionary/ordered.lux
new file mode 100644
index 000000000..adbb1303f
--- /dev/null
+++ b/stdlib/source/documentation/lux/data/collection/dictionary/ordered.lux
@@ -0,0 +1,84 @@
+(.module:
+ [library
+ [lux #*
+ ["$" documentation (#+ documentation:)]
+ [control
+ ["<>" parser
+ ["<.>" code]]]
+ [data
+ ["." text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ [syntax (#+ syntax:)]
+ ["." code]
+ ["." template]]]]
+ [\\library
+ ["." /]])
+
+(documentation: /.Dictionary
+ "A dictionary data-structure with ordered entries.")
+
+(documentation: /.empty
+ "An empty dictionary, employing the given order."
+ [(empty order)])
+
+(documentation: /.value
+ ""
+ [(value key dict)])
+
+(documentation: /.key?
+ ""
+ [(key? dict key)])
+
+(template [<name>]
+ [(`` (documentation: <name>
+ (format "Yields value under the " (~~ (template.text [<name>])) "imum key.")
+ [(<name> dict)]))]
+
+ [/.min]
+ [/.max]
+ )
+
+(documentation: /.size
+ ""
+ [(size dict)])
+
+(documentation: /.has
+ ""
+ [(has key value dict)])
+
+(documentation: /.lacks
+ ""
+ [(lacks key dict)])
+
+(documentation: /.revised
+ ""
+ [(revised key transform dict)])
+
+(documentation: /.of_list
+ ""
+ [(of_list order list)])
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..Dictionary
+ ..empty
+ ..value
+ ..key?
+
+ ..min
+ ..max
+
+ ..size
+ ..has
+ ..lacks
+ ..revised
+ ..of_list
+ ($.default /.empty?)
+ ($.default /.entries)
+ ($.default /.keys)
+ ($.default /.values)
+ ($.default /.equivalence)]
+ []))
diff --git a/stdlib/source/documentation/lux/data/collection/dictionary/plist.lux b/stdlib/source/documentation/lux/data/collection/dictionary/plist.lux
new file mode 100644
index 000000000..2450cc9eb
--- /dev/null
+++ b/stdlib/source/documentation/lux/data/collection/dictionary/plist.lux
@@ -0,0 +1,58 @@
+(.module:
+ [library
+ [lux #*
+ ["$" documentation (#+ documentation:)]
+ [control
+ ["<>" parser
+ ["<.>" code]]]
+ [data
+ ["." text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ [syntax (#+ syntax:)]
+ ["." code]
+ ["." template]]]]
+ [\\library
+ ["." /]])
+
+(documentation: /.PList
+ (format "A property list."
+ \n "It's a simple dictionary-like structure with Text keys."))
+
+(documentation: /.value
+ ""
+ [(value key properties)])
+
+(documentation: /.contains?
+ ""
+ [(contains? key properties)])
+
+(documentation: /.has
+ ""
+ [(has key val properties)])
+
+(documentation: /.revised
+ ""
+ [(revised key f properties)])
+
+(documentation: /.lacks
+ ""
+ [(lacks key properties)])
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..PList
+ ..value
+ ..contains?
+ ..has
+ ..revised
+ ..lacks
+ ($.default /.empty)
+ ($.default /.size)
+ ($.default /.empty?)
+ ($.default /.keys)
+ ($.default /.values)
+ ($.default /.equivalence)]
+ []))
diff --git a/stdlib/source/documentation/lux/data/collection/list.lux b/stdlib/source/documentation/lux/data/collection/list.lux
new file mode 100644
index 000000000..1050ab7ce
--- /dev/null
+++ b/stdlib/source/documentation/lux/data/collection/list.lux
@@ -0,0 +1,239 @@
+(.module:
+ [library
+ [lux (#- example)
+ ["$" documentation (#+ documentation:)]
+ [control
+ ["<>" parser
+ ["<.>" code]]]
+ [data
+ ["." text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ [syntax (#+ syntax:)]
+ ["." code]
+ ["." template]]]]
+ [\\library
+ ["." /]])
+
+(documentation: /.aggregates
+ ""
+ [(aggregates f init inputs)])
+
+(documentation: /.reversed
+ ""
+ [(reversed xs)])
+
+(documentation: /.only
+ "A list with only values that satisfy the predicate."
+ [(only keep? xs)])
+
+(documentation: /.partition
+ "Divide the list into all elements that satisfy a predicate, and all elements that do not."
+ [(partition satisfies? list)])
+
+(documentation: /.pairs
+ (format "Cut the list into pairs of 2."
+ \n "Caveat emptor: If the list has an un-even number of elements, the last one will be skipped.")
+ [(pairs xs)])
+
+(template [<name>]
+ [(documentation: <name>
+ ""
+ [(<name> n xs)])]
+
+ [/.first]
+ [/.after]
+ )
+
+(template [<name>]
+ [(documentation: <name>
+ ""
+ [(<name> predicate xs)])]
+
+ [/.while]
+ [/.until]
+ )
+
+(documentation: /.split_at
+ ""
+ [(split_at n xs)])
+
+(documentation: /.split_when
+ "Segment the list by using a predicate to tell when to cut."
+ [(split_when predicate xs)])
+
+(documentation: /.sub
+ "Segment the list into sub-lists of (at most) the given size."
+ [(sub size list)])
+
+(documentation: /.repeated
+ "A list of the value x, repeated n times."
+ [(repeated n x)])
+
+(documentation: /.iterations
+ "Generates a list element by element until the function returns #.None."
+ [(iterations f x)])
+
+(documentation: /.one
+ ""
+ [(one check xs)])
+
+(documentation: /.all
+ ""
+ [(all check xs)])
+
+(documentation: /.example
+ "Yields the first value in the list that satisfies the predicate."
+ [(example predicate xs)])
+
+(documentation: /.interposed
+ "Puts a value between every two elements in the list."
+ [(interposed sep xs)])
+
+(documentation: /.size
+ ""
+ [(size list)])
+
+(template [<name>]
+ [(documentation: <name>
+ ""
+ [(<name> predicate items)])]
+
+ [/.every?]
+ [/.any?]
+ )
+
+(documentation: /.item
+ "Fetches the element at the specified index."
+ [(item i xs)])
+
+(documentation: /.sorted
+ "A list ordered by a comparison function."
+ [(sorted < xs)])
+
+(documentation: /.empty?
+ ""
+ [(empty? xs)])
+
+(documentation: /.member?
+ ""
+ [(member? eq xs x)])
+
+(template [<name> <doc>]
+ [(documentation: <name>
+ <doc>
+ [(<name> xs)])]
+
+ [/.head "Yields the first element of a list."]
+ [/.tail "For a list of size N, yields the N-1 elements after the first one."]
+ )
+
+(documentation: /.indices
+ "Produces all the valid indices for a given size."
+ [(indices size)])
+
+(documentation: /.zipped
+ "Create list zippers with the specified number of input lists."
+ [(def: zipped/2 (zipped 2))
+ (def: zipped/3 (zipped 3))
+ (zipped/3 xs ys zs)
+ ((zipped 3) xs ys zs)])
+
+(documentation: /.zipped_with
+ "Create list zippers with the specified number of input lists."
+ [(def: zipped_with/2 (zipped_with 2))
+ (def: zipped_with/3 (zipped_with 3))
+ (zipped_with/2 + xs ys)
+ ((zipped_with 2) + xs ys)])
+
+(documentation: /.last
+ ""
+ [(last xs)])
+
+(documentation: /.inits
+ (format "For a list of size N, yields the first N-1 elements."
+ \n "Will yield a #.None for empty lists.")
+ [(inits xs)])
+
+(documentation: /.together
+ "The sequential combination of all the lists.")
+
+(documentation: /.with
+ "Enhances a monad with List functionality."
+ [(with monad)])
+
+(documentation: /.lifted
+ "Wraps a monadic value with List machinery."
+ [(lifted monad)])
+
+(documentation: /.enumeration
+ "Pairs every element in the list with its index, starting at 0."
+ [(enumeration xs)])
+
+(documentation: /.when
+ "Can be used as a guard in (co)monadic be/do expressions."
+ [(do monad
+ [value (do_something 1 2 3)
+ /.when (passes_test? value)]
+ (do_something_else 4 5 6))])
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..aggregates
+ ..reversed
+ ..only
+ ..partition
+ ..pairs
+
+ ..first
+ ..after
+
+ ..while
+ ..until
+
+ ..split_at
+ ..split_when
+ ..sub
+ ..repeated
+ ..iterations
+ ..one
+ ..all
+ ..example
+ ..interposed
+ ..size
+
+ ..every?
+ ..any?
+
+ ..item
+ ..sorted
+ ..empty?
+ ..member?
+
+ ..head
+ ..tail
+
+ ..indices
+ ..zipped
+ ..zipped_with
+ ..last
+ ..inits
+ ..together
+ ..with
+ ..lifted
+ ..enumeration
+ ..when
+ ($.default /.fold)
+ ($.default /.equivalence)
+ ($.default /.hash)
+ ($.default /.monoid)
+ ($.default /.functor)
+ ($.default /.apply)
+ ($.default /.monad)
+ ($.default /.zipped/2)
+ ($.default /.zipped/3)
+ ($.default /.zipped_with/2)
+ ($.default /.zipped_with/3)]
+ []))
diff --git a/stdlib/source/documentation/lux/data/collection/queue.lux b/stdlib/source/documentation/lux/data/collection/queue.lux
new file mode 100644
index 000000000..5b866fe90
--- /dev/null
+++ b/stdlib/source/documentation/lux/data/collection/queue.lux
@@ -0,0 +1,62 @@
+(.module:
+ [library
+ [lux (#- list)
+ ["$" documentation (#+ documentation:)]
+ [control
+ ["<>" parser
+ ["<.>" code]]]
+ [data
+ ["." text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ [syntax (#+ syntax:)]
+ ["." code]
+ ["." template]]]]
+ [\\library
+ ["." /]]
+ ["." / #_
+ ["#." priority]])
+
+(documentation: /.Queue
+ "A first-in, first-out sequential data-structure.")
+
+(documentation: /.of_list
+ ""
+ [(of_list entries)])
+
+(documentation: /.list
+ ""
+ [(list queue)])
+
+(documentation: /.front
+ "Yields the first value in the queue, if any.")
+
+(documentation: /.member?
+ ""
+ [(member? equivalence queue member)])
+
+(documentation: /.next
+ ""
+ [(next queue)])
+
+(documentation: /.end
+ ""
+ [(end val queue)])
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..Queue
+ ..of_list
+ ..list
+ ..front
+ ..member?
+ ..next
+ ..end
+ ($.default /.empty)
+ ($.default /.size)
+ ($.default /.empty?)
+ ($.default /.equivalence)
+ ($.default /.functor)]
+ [/priority.documentation]))
diff --git a/stdlib/source/documentation/lux/data/collection/queue/priority.lux b/stdlib/source/documentation/lux/data/collection/queue/priority.lux
new file mode 100644
index 000000000..e62869ecd
--- /dev/null
+++ b/stdlib/source/documentation/lux/data/collection/queue/priority.lux
@@ -0,0 +1,41 @@
+(.module:
+ [library
+ [lux (#- list)
+ ["$" documentation (#+ documentation:)]
+ [control
+ ["<>" parser
+ ["<.>" code]]]
+ [data
+ ["." text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ [syntax (#+ syntax:)]
+ ["." code]
+ ["." template]]]]
+ [\\library
+ ["." /]])
+
+(documentation: /.member?
+ ""
+ [(member? equivalence queue member)])
+
+(documentation: /.end
+ ""
+ [(end priority value queue)])
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..member?
+ ..end
+ ($.default /.Priority)
+ ($.default /.max)
+ ($.default /.min)
+ ($.default /.Queue)
+ ($.default /.empty)
+ ($.default /.front)
+ ($.default /.size)
+ ($.default /.next)
+ ($.default /.empty?)]
+ []))
diff --git a/stdlib/source/documentation/lux/data/collection/row.lux b/stdlib/source/documentation/lux/data/collection/row.lux
new file mode 100644
index 000000000..e72e8974e
--- /dev/null
+++ b/stdlib/source/documentation/lux/data/collection/row.lux
@@ -0,0 +1,86 @@
+(.module:
+ [library
+ [lux (#- list)
+ ["$" documentation (#+ documentation:)]
+ [control
+ ["<>" parser
+ ["<.>" code]]]
+ [data
+ ["." text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ [syntax (#+ syntax:)]
+ ["." code]
+ ["." template]]]]
+ [\\library
+ ["." /]])
+
+(documentation: /.Row
+ "A sequential data-structure with fast random access.")
+
+(documentation: /.suffix
+ ""
+ [(suffix val row)])
+
+(documentation: /.within_bounds?
+ "Determines whether the index is within the bounds of the row."
+ [(within_bounds? row idx)])
+
+(documentation: /.item
+ ""
+ [(item idx row)])
+
+(documentation: /.has
+ ""
+ [(has idx val row)])
+
+(documentation: /.revised
+ ""
+ [(revised idx f row)])
+
+(documentation: /.prefix
+ ""
+ [(prefix row)])
+
+(documentation: /.list
+ ""
+ [(list row)])
+
+(documentation: /.member?
+ ""
+ [(member? equivalence row val)])
+
+(documentation: /.row
+ "Row literals."
+ [(: (Row Nat)
+ (row 12 34 56 78 90))])
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..Row
+ ..suffix
+ ..within_bounds?
+ ..item
+ ..has
+ ..revised
+ ..prefix
+ ..list
+ ..member?
+ ..row
+ ($.default /.empty)
+ ($.default /.size)
+ ($.default /.index_out_of_bounds)
+ ($.default /.of_list)
+ ($.default /.empty?)
+ ($.default /.equivalence)
+ ($.default /.fold)
+ ($.default /.monoid)
+ ($.default /.functor)
+ ($.default /.apply)
+ ($.default /.monad)
+ ($.default /.reversed)
+ ($.default /.every?)
+ ($.default /.any?)]
+ []))
diff --git a/stdlib/source/documentation/lux/data/collection/sequence.lux b/stdlib/source/documentation/lux/data/collection/sequence.lux
new file mode 100644
index 000000000..64e976155
--- /dev/null
+++ b/stdlib/source/documentation/lux/data/collection/sequence.lux
@@ -0,0 +1,98 @@
+(.module:
+ [library
+ [lux (#- list)
+ ["$" documentation (#+ documentation:)]
+ [control
+ ["<>" parser
+ ["<.>" code]]]
+ [data
+ ["." text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ [syntax (#+ syntax:)]
+ ["." code]
+ ["." template]]]]
+ [\\library
+ ["." /]])
+
+(documentation: /.Sequence
+ "An infinite sequence of values.")
+
+(documentation: /.iterations
+ "A stateful way of infinitely calculating the values of a sequence."
+ [(iterations step init)])
+
+(documentation: /.repeated
+ "Repeat a value forever."
+ [(repeated x)])
+
+(documentation: /.cycle
+ (format "Go over the elements of a list forever."
+ \n "The list should not be empty.")
+ [(cycle [start next])])
+
+(documentation: /.item
+ ""
+ [(item idx sequence)])
+
+(template [<taker> <dropper>]
+ [(documentation: <taker>
+ ""
+ [(<taker> pred xs)])
+ (documentation: <dropper>
+ ""
+ [(<dropper> pred xs)])]
+
+ [/.while /.until]
+ [/.first /.after]
+ )
+
+(template [<splitter>]
+ [(documentation: <splitter>
+ ""
+ [(<splitter> pred xs)])]
+
+ [/.split_when]
+ [/.split_at]
+ )
+
+(documentation: /.only
+ "A new sequence only with items that satisfy the predicate."
+ [(only predicate sequence)])
+
+(documentation: /.partition
+ (format "Split a sequence in two based on a predicate."
+ \n "The left side contains all entries for which the predicate is #1."
+ \n "The right side contains all entries for which the predicate is #0.")
+ [(partition left? xs)])
+
+(documentation: /.^sequence&
+ (format "Allows destructuring of sequences in pattern-matching expressions."
+ \n "Caveat emptor: Only use it for destructuring, and not for testing values within the sequences.")
+ [(let [(^sequence& x y z _tail) (some_sequence_func +1 +2 +3)]
+ (func x y z))])
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..Sequence
+ ..iterations
+ ..repeated
+ ..cycle
+ ..item
+
+ ..while ..until
+ ..first ..after
+
+ ..split_when
+ ..split_at
+
+ ..only
+ ..partition
+ ..^sequence&
+ ($.default /.head)
+ ($.default /.tail)
+ ($.default /.functor)
+ ($.default /.comonad)]
+ []))
diff --git a/stdlib/source/documentation/lux/data/color.lux b/stdlib/source/documentation/lux/data/color.lux
new file mode 100644
index 000000000..96a44b6ed
--- /dev/null
+++ b/stdlib/source/documentation/lux/data/color.lux
@@ -0,0 +1,126 @@
+(.module:
+ [library
+ [lux #*
+ ["$" documentation (#+ documentation:)]
+ [control
+ ["<>" parser
+ ["<.>" code]]]
+ [data
+ ["." text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ [syntax (#+ syntax:)]
+ ["." code]
+ ["." template]]]]
+ [\\library
+ ["." /]]
+ ["." / #_
+ ["#." named]])
+
+(documentation: /.RGB
+ "Red-Green-Blue color format.")
+
+(documentation: /.HSL
+ "Hue-Saturation-Lightness color format.")
+
+(documentation: /.CMYK
+ "Cyan-Magenta-Yellow-Key color format.")
+
+(documentation: /.HSB
+ "Hue-Saturation-Brightness color format.")
+
+(documentation: /.Color
+ "A color value, independent of color format.")
+
+(documentation: /.complement
+ "The opposite color."
+ [(complement color)])
+
+(documentation: /.interpolated
+ ""
+ [(interpolated ratio end start)])
+
+(template [<name>]
+ [(documentation: <name>
+ ""
+ [(<name> ratio color)])]
+
+ [/.darker]
+ [/.brighter]
+ [/.saturated]
+ [/.un_saturated]
+ )
+
+(syntax: (palette_documentation [[_ name] <code>.identifier])
+ (in (list (code.text (format "A " (text.replaced "_" "-" name) " palette.")))))
+
+(documentation: /.analogous
+ (palette_documentation /.analogous)
+ [(analogous spread variations color)])
+
+(documentation: /.monochromatic
+ (palette_documentation /.monochromatic)
+ [(monochromatic spread variations color)])
+
+(documentation: /.Alpha
+ "The degree of transparency of a pigment.")
+
+(documentation: /.transparent
+ "The maximum degree of transparency.")
+
+(documentation: /.translucent
+ "The average degree of transparency.")
+
+(documentation: /.opaque
+ "The minimum degree of transparency.")
+
+(documentation: /.Pigment
+ "A color with some degree of transparency.")
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..RGB
+ ..HSL
+ ..CMYK
+ ..HSB
+ ..Color
+ ..complement
+ ..interpolated
+
+ ..darker
+ ..brighter
+ ..saturated
+ ..un_saturated
+
+ ..analogous
+ ..monochromatic
+ ..Alpha
+ ..transparent
+ ..translucent
+ ..opaque
+ ..Pigment
+ ($.default /.of_rgb)
+ ($.default /.rgb)
+ ($.default /.equivalence)
+ ($.default /.hash)
+ ($.default /.black)
+ ($.default /.white)
+ ($.default /.addition)
+ ($.default /.subtraction)
+ ($.default /.hsl)
+ ($.default /.of_hsl)
+ ($.default /.hsb)
+ ($.default /.of_hsb)
+ ($.default /.cmyk)
+ ($.default /.of_cmyk)
+ ($.default /.gray_scale)
+ ($.default /.triad)
+ ($.default /.clash)
+ ($.default /.split_complement)
+ ($.default /.square)
+ ($.default /.tetradic)
+ ($.default /.Spread)
+ ($.default /.Palette)]
+ [/named.documentation]))
diff --git a/stdlib/source/documentation/lux/data/color/named.lux b/stdlib/source/documentation/lux/data/color/named.lux
new file mode 100644
index 000000000..6f9a080eb
--- /dev/null
+++ b/stdlib/source/documentation/lux/data/color/named.lux
@@ -0,0 +1,319 @@
+(.module:
+ [library
+ [lux #*
+ ["$" documentation (#+ documentation:)]
+ [control
+ ["<>" parser
+ ["<.>" code]]]
+ [data
+ ["." text (#+ \n)
+ ["%" format (#+ format)]]]
+ [macro
+ [syntax (#+ syntax:)]
+ ["." code]
+ ["." template]]
+ [math
+ [number
+ ["." nat ("#\." hex)]]]]]
+ [\\library
+ ["." /
+ ["/#" //]]])
+
+(template [<name>]
+ [(documentation: <name>
+ (let [[red green blue] (//.rgb <name>)
+ [_ name] (name_of <name>)]
+ (format "R:" (nat\encode red)
+ " G:" (nat\encode green)
+ " B:" (nat\encode blue)
+ " | " (text.replaced "_" " " name))))]
+
+ [/.alice_blue]
+ [/.antique_white]
+ [/.aqua]
+ [/.aquamarine]
+ [/.azure]
+ [/.beige]
+ [/.bisque]
+ [/.black]
+ [/.blanched_almond]
+ [/.blue]
+ [/.blue_violet]
+ [/.brown]
+ [/.burly_wood]
+ [/.cadet_blue]
+ [/.chartreuse]
+ [/.chocolate]
+ [/.coral]
+ [/.cornflower_blue]
+ [/.cornsilk]
+ [/.crimson]
+ [/.cyan]
+ [/.dark_blue]
+ [/.dark_cyan]
+ [/.dark_goldenrod]
+ [/.dark_gray]
+ [/.dark_green]
+ [/.dark_khaki]
+ [/.dark_magenta]
+ [/.dark_olive_green]
+ [/.dark_orange]
+ [/.dark_orchid]
+ [/.dark_red]
+ [/.dark_salmon]
+ [/.dark_sea_green]
+ [/.dark_slate_blue]
+ [/.dark_slate_gray]
+ [/.dark_turquoise]
+ [/.dark_violet]
+ [/.deep_pink]
+ [/.deep_sky_blue]
+ [/.dim_gray]
+ [/.dodger_blue]
+ [/.fire_brick]
+ [/.floral_white]
+ [/.forest_green]
+ [/.fuchsia]
+ [/.gainsboro]
+ [/.ghost_white]
+ [/.gold]
+ [/.goldenrod]
+ [/.gray]
+ [/.green]
+ [/.green_yellow]
+ [/.honey_dew]
+ [/.hot_pink]
+ [/.indian_red]
+ [/.indigo]
+ [/.ivory]
+ [/.khaki]
+ [/.lavender]
+ [/.lavender_blush]
+ [/.lawn_green]
+ [/.lemon_chiffon]
+ [/.light_blue]
+ [/.light_coral]
+ [/.light_cyan]
+ [/.light_goldenrod_yellow]
+ [/.light_gray]
+ [/.light_green]
+ [/.light_pink]
+ [/.light_salmon]
+ [/.light_sea_green]
+ [/.light_sky_blue]
+ [/.light_slate_gray]
+ [/.light_steel_blue]
+ [/.light_yellow]
+ [/.lime]
+ [/.lime_green]
+ [/.linen]
+ [/.magenta]
+ [/.maroon]
+ [/.medium_aquamarine]
+ [/.medium_blue]
+ [/.medium_orchid]
+ [/.medium_purple]
+ [/.medium_sea_green]
+ [/.medium_slate_blue]
+ [/.medium_spring_green]
+ [/.medium_turquoise]
+ [/.medium_violet_red]
+ [/.midnight_blue]
+ [/.mint_cream]
+ [/.misty_rose]
+ [/.moccasin]
+ [/.navajo_white]
+ [/.navy]
+ [/.old_lace]
+ [/.olive]
+ [/.olive_drab]
+ [/.orange]
+ [/.orange_red]
+ [/.orchid]
+ [/.pale_goldenrod]
+ [/.pale_green]
+ [/.pale_turquoise]
+ [/.pale_violet_red]
+ [/.papaya_whip]
+ [/.peach_puff]
+ [/.peru]
+ [/.pink]
+ [/.plum]
+ [/.powder_blue]
+ [/.purple]
+ [/.rebecca_purple]
+ [/.red]
+ [/.rosy_brown]
+ [/.royal_blue]
+ [/.saddle_brown]
+ [/.salmon]
+ [/.sandy_brown]
+ [/.sea_green]
+ [/.sea_shell]
+ [/.sienna]
+ [/.silver]
+ [/.sky_blue]
+ [/.slate_blue]
+ [/.slate_gray]
+ [/.snow]
+ [/.spring_green]
+ [/.steel_blue]
+ [/.tan]
+ [/.teal]
+ [/.thistle]
+ [/.tomato]
+ [/.turquoise]
+ [/.violet]
+ [/.wheat]
+ [/.white]
+ [/.white_smoke]
+ [/.yellow]
+ [/.yellow_green]
+ )
+
+(.def: .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [..alice_blue
+ ..antique_white
+ ..aqua
+ ..aquamarine
+ ..azure
+ ..beige
+ ..bisque
+ ..black
+ ..blanched_almond
+ ..blue
+ ..blue_violet
+ ..brown
+ ..burly_wood
+ ..cadet_blue
+ ..chartreuse
+ ..chocolate
+ ..coral
+ ..cornflower_blue
+ ..cornsilk
+ ..crimson
+ ..cyan
+ ..dark_blue
+ ..dark_cyan
+ ..dark_goldenrod
+ ..dark_gray
+ ..dark_green
+ ..dark_khaki
+ ..dark_magenta
+ ..dark_olive_green
+ ..dark_orange
+ ..dark_orchid
+ ..dark_red
+ ..dark_salmon
+ ..dark_sea_green
+ ..dark_slate_blue
+ ..dark_slate_gray
+ ..dark_turquoise
+ ..dark_violet
+ ..deep_pink
+ ..deep_sky_blue
+ ..dim_gray
+ ..dodger_blue
+ ..fire_brick
+ ..floral_white
+ ..forest_green
+ ..fuchsia
+ ..gainsboro
+ ..ghost_white
+ ..gold
+ ..goldenrod
+ ..gray
+ ..green
+ ..green_yellow
+ ..honey_dew
+ ..hot_pink
+ ..indian_red
+ ..indigo
+ ..ivory
+ ..khaki
+ ..lavender
+ ..lavender_blush
+ ..lawn_green
+ ..lemon_chiffon
+ ..light_blue
+ ..light_coral
+ ..light_cyan
+ ..light_goldenrod_yellow
+ ..light_gray
+ ..light_green
+ ..light_pink
+ ..light_salmon
+ ..light_sea_green
+ ..light_sky_blue
+ ..light_slate_gray
+ ..light_steel_blue
+ ..light_yellow
+ ..lime
+ ..lime_green
+ ..linen
+ ..magenta
+ ..maroon
+ ..medium_aquamarine
+ ..medium_blue
+ ..medium_orchid
+ ..medium_purple
+ ..medium_sea_green
+ ..medium_slate_blue
+ ..medium_spring_green
+ ..medium_turquoise
+ ..medium_violet_red
+ ..midnight_blue
+ ..mint_cream
+ ..misty_rose
+ ..moccasin
+ ..navajo_white
+ ..navy
+ ..old_lace
+ ..olive
+ ..olive_drab
+ ..orange
+ ..orange_red
+ ..orchid
+ ..pale_goldenrod
+ ..pale_green
+ ..pale_turquoise
+ ..pale_violet_red
+ ..papaya_whip
+ ..peach_puff
+ ..peru
+ ..pink
+ ..plum
+ ..powder_blue
+ ..purple
+ ..rebecca_purple
+ ..red
+ ..rosy_brown
+ ..royal_blue
+ ..saddle_brown
+ ..salmon
+ ..sandy_brown
+ ..sea_green
+ ..sea_shell
+ ..sienna
+ ..silver
+ ..sky_blue
+ ..slate_blue
+ ..slate_gray
+ ..snow
+ ..spring_green
+ ..steel_blue
+ ..tan
+ ..teal
+ ..thistle
+ ..tomato
+ ..turquoise
+ ..violet
+ ..wheat
+ ..white
+ ..white_smoke
+ ..yellow
+ ..yellow_green]
+ []))