aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/documentation/lux/control
diff options
context:
space:
mode:
Diffstat (limited to '')
-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
9 files changed, 691 insertions, 20 deletions
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)]
+ []))