diff options
Diffstat (limited to 'stdlib/source/documentation')
34 files changed, 1487 insertions, 51 deletions
diff --git a/stdlib/source/documentation/lux/abstract.lux b/stdlib/source/documentation/lux/abstract.lux index 9cc80dcac..a8c0d3b03 100644 --- a/stdlib/source/documentation/lux/abstract.lux +++ b/stdlib/source/documentation/lux/abstract.lux @@ -24,7 +24,7 @@ (.def: .public documentation (.List $.Module) - (list.joined + (list.together (list /apply.documentation /codec.documentation /comonad.documentation diff --git a/stdlib/source/documentation/lux/abstract/comonad.lux b/stdlib/source/documentation/lux/abstract/comonad.lux index f1e220593..5ae976a63 100644 --- a/stdlib/source/documentation/lux/abstract/comonad.lux +++ b/stdlib/source/documentation/lux/abstract/comonad.lux @@ -18,7 +18,7 @@ "A co-monadic parallel to the 'do' macro." [(let [square (function (_ n) (* n n))] (be comonad - [inputs (iterate inc +2)] + [inputs (iterate ++ +2)] (square (out inputs))))]) (.def: .public documentation diff --git a/stdlib/source/documentation/lux/abstract/interval.lux b/stdlib/source/documentation/lux/abstract/interval.lux index f4c57de2a..7162f9ee9 100644 --- a/stdlib/source/documentation/lux/abstract/interval.lux +++ b/stdlib/source/documentation/lux/abstract/interval.lux @@ -11,6 +11,10 @@ (documentation: /.Interval "A representation of top and bottom boundaries for an ordered type.") +(documentation: /.singleton + "An interval where both top and bottom are the same value." + [(singleton enum elem)]) + (documentation: /.borders? "Where a value is at the border of an interval.") @@ -31,13 +35,13 @@ ($.module /._ "" [..Interval + ..singleton ..borders? ..union ..intersection ..complement ..meets? ($.default /.between) - ($.default /.singleton) ($.default /.inner?) ($.default /.outer?) ($.default /.singleton?) diff --git a/stdlib/source/documentation/lux/abstract/monad.lux b/stdlib/source/documentation/lux/abstract/monad.lux index dd472057d..2d55ff0c5 100644 --- a/stdlib/source/documentation/lux/abstract/monad.lux +++ b/stdlib/source/documentation/lux/abstract/monad.lux @@ -21,9 +21,9 @@ z (f2 z)] (in (f3 z)))]) -(documentation: /.bind +(documentation: /.then "Apply a function with monadic effects to a monadic value and yield a new monadic value." - [(bind monad function)]) + [(then monad function)]) (documentation: /.seq "Run all the monadic values in the list and produce a list of the base values." @@ -47,7 +47,7 @@ "" [..Monad ..do - ..bind + ..then ..seq ..map ..only diff --git a/stdlib/source/documentation/lux/control.lux b/stdlib/source/documentation/lux/control.lux index 4fcbe7a98..3a1f688a9 100644 --- a/stdlib/source/documentation/lux/control.lux +++ b/stdlib/source/documentation/lux/control.lux @@ -16,30 +16,21 @@ ["#." io] ["#." lazy] ["#." maybe] - ... ["#." parser] - ... ["#." pipe] - ... ["#." reader] - ... ["#." region] - ... ["#." remember] - ... [security - ... ["#." policy] - ... ["#." capability]] - ... ["#." state] - ... ["#." thread] - ... ["#." try] - ... ["#." writer] + ["#." parser] + ["#." pipe] + ["#." reader] + ["#." region] + ["#." remember] + ["#." security] + ["#." state] + ["#." thread] + ["#." try] + ["#." writer] ]) -... (def: security -... Test -... ($_ _.and -... /policy.documentation -... /capability.documentation -... )) - (.def: .public documentation (.List $.Module) - (list.joined + (list.together (list /concatenative.documentation /concurrency.documentation /continuation.documentation @@ -48,14 +39,14 @@ /io.documentation /lazy.documentation /maybe.documentation - ... /parser.documentation - ... /pipe.documentation - ... /reader.documentation - ... /region.documentation - ... /remember.documentation - ... ..security - ... /state.documentation - ... /thread.documentation - ... /try.documentation - ... /writer.documentation + /parser.documentation + /pipe.documentation + /reader.documentation + /region.documentation + /remember.documentation + /security.documentation + /state.documentation + /thread.documentation + /try.documentation + /writer.documentation ))) diff --git a/stdlib/source/documentation/lux/control/concatenative.lux b/stdlib/source/documentation/lux/control/concatenative.lux index 495bc5512..6c97e056f 100644 --- a/stdlib/source/documentation/lux/control/concatenative.lux +++ b/stdlib/source/documentation/lux/control/concatenative.lux @@ -51,7 +51,7 @@ (documentation: /.apply "A generator for functions that turn arity N functions into arity N concatenative functions." [(: (=> [Nat] [Nat]) - ((apply 1) inc))]) + ((apply 1) ++))]) (template [<arity>] [(with_expansions [<name> (template.identifier [/._] ["apply/" <arity>]) @@ -167,7 +167,7 @@ (documentation: /.do "Do-while loop expression." - [(n.= (inc sample) + [(n.= (++ sample) (||> (push sample) (push (push false)) (push (|>> (push 1) n/+)) diff --git a/stdlib/source/documentation/lux/control/concurrency.lux b/stdlib/source/documentation/lux/control/concurrency.lux index f9b751494..1408c984a 100644 --- a/stdlib/source/documentation/lux/control/concurrency.lux +++ b/stdlib/source/documentation/lux/control/concurrency.lux @@ -18,7 +18,7 @@ (.def: .public documentation (.List $.Module) - (list.joined + (list.together (list /actor.documentation /async.documentation /atom.documentation diff --git a/stdlib/source/documentation/lux/control/concurrency/actor.lux b/stdlib/source/documentation/lux/control/concurrency/actor.lux index 29513888c..6f9327a9a 100644 --- a/stdlib/source/documentation/lux/control/concurrency/actor.lux +++ b/stdlib/source/documentation/lux/control/concurrency/actor.lux @@ -87,7 +87,7 @@ [(actor {Nat 123} ((on_mail message state self) - (message (inc state) self)))]) + (message (++ state) self)))]) (documentation: /.message: (format "A message can access the actor's state through the state parameter." diff --git a/stdlib/source/documentation/lux/control/concurrency/async.lux b/stdlib/source/documentation/lux/control/concurrency/async.lux index 2842ed06b..823967b36 100644 --- a/stdlib/source/documentation/lux/control/concurrency/async.lux +++ b/stdlib/source/documentation/lux/control/concurrency/async.lux @@ -59,17 +59,17 @@ \n "Returns an async that will eventually host its result.") [(future computation)]) -(documentation: /.delayed +(documentation: /.after "Delivers a value after a certain period has passed." - [(delayed milli_seconds value)]) + [(after milli_seconds value)]) (documentation: /.delay "An async that will be resolved after the specified amount of milli-seconds." [(delay milli_seconds)]) -(documentation: /.time_out +(documentation: /.within "Wait for an async to be resolved within the specified amount of milli-seconds." - [(time_out milli_seconds async)]) + [(within milli_seconds async)]) (.def: .public documentation (.List $.Module) @@ -87,9 +87,9 @@ ..either ..schedule! ..future - ..delayed + ..after ..delay - ..time_out + ..within ($.default /.functor) ($.default /.apply) ($.default /.monad)] diff --git a/stdlib/source/documentation/lux/control/concurrency/frp.lux b/stdlib/source/documentation/lux/control/concurrency/frp.lux index 71f740782..2500b119d 100644 --- a/stdlib/source/documentation/lux/control/concurrency/frp.lux +++ b/stdlib/source/documentation/lux/control/concurrency/frp.lux @@ -57,7 +57,7 @@ ($.default /.apply) ($.default /.monad) ($.default /.subscribe!) - ($.default /.folds) + ($.default /.aggregates) ($.default /.poll) ($.default /.periodic) ($.default /.iterations) diff --git a/stdlib/source/documentation/lux/control/exception.lux b/stdlib/source/documentation/lux/control/exception.lux index ec225630a..fae2b0163 100644 --- a/stdlib/source/documentation/lux/control/exception.lux +++ b/stdlib/source/documentation/lux/control/exception.lux @@ -63,7 +63,7 @@ (.def: .public documentation (.List $.Module) ($.module /._ - "" + "Pure-Lux exception-handling functionality." [..Exception ..match? ..when diff --git a/stdlib/source/documentation/lux/control/function.lux b/stdlib/source/documentation/lux/control/function.lux index 889cc8655..88556dda7 100644 --- a/stdlib/source/documentation/lux/control/function.lux +++ b/stdlib/source/documentation/lux/control/function.lux @@ -8,7 +8,12 @@ [macro ["." template]]]] [\\library - ["." /]]) + ["." /]] + ["." / #_ + ["#." contract] + ["#." memo] + ["#." mixin] + ["#." mutual]]) (documentation: /.identity (format "Identity function." @@ -45,4 +50,7 @@ ..flipped ..apply ($.default /.monoid)] - [])) + [/contract.documentation + /memo.documentation + /mixin.documentation + /mutual.documentation])) diff --git a/stdlib/source/documentation/lux/control/function/contract.lux b/stdlib/source/documentation/lux/control/function/contract.lux new file mode 100644 index 000000000..84ef6ad13 --- /dev/null +++ b/stdlib/source/documentation/lux/control/function/contract.lux @@ -0,0 +1,36 @@ +(.module: + [library + [lux (#- if loop) + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(documentation: /.pre + (format "Pre-conditions." + \n "Given a test and an expression to run, only runs the expression if the test passes." + \n "Otherwise, an error is raised.") + [(pre (i.= +4 (i.+ +2 +2)) + (foo +123 +456 +789))]) + +(documentation: /.post + (format "Post-conditions." + \n "Given a predicate and an expression to run, evaluates the expression and then tests the output with the predicate." + \n "If the predicate returns #1, returns the value of the expression." + \n "Otherwise, an error is raised.") + [(post i.even? + (i.+ +2 +2))]) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..pre + ..post + ($.default /.pre_condition_failed) + ($.default /.post_condition_failed)] + [])) diff --git a/stdlib/source/documentation/lux/control/function/memo.lux b/stdlib/source/documentation/lux/control/function/memo.lux new file mode 100644 index 000000000..823b49772 --- /dev/null +++ b/stdlib/source/documentation/lux/control/function/memo.lux @@ -0,0 +1,36 @@ +(.module: + [library + [lux (#- if loop) + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(documentation: /.open + "Memoization where the memoized results can be re-used accross invocations." + [(open memo)]) + +(documentation: /.closed + (format "Memoization confined to a single invocation to the function (not counting any subsequent recursive invocations)." + \n "Memoized results will be re-used during recursive invocations, but cannot be accessed after the main invocation has ended.") + [(closed hash memo)]) + +(documentation: /.none + (format "No memoization at all." + \n "This is useful as a test control when measuring the effect of using memoization.") + [(none hash memo)]) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..open + ..closed + ..none + ($.default /.memoization) + ($.default /.Memo)] + [])) diff --git a/stdlib/source/documentation/lux/control/function/mixin.lux b/stdlib/source/documentation/lux/control/function/mixin.lux new file mode 100644 index 000000000..f23f065b0 --- /dev/null +++ b/stdlib/source/documentation/lux/control/function/mixin.lux @@ -0,0 +1,60 @@ +(.module: + [library + [lux (#- if loop) + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(documentation: /.Mixin + "A partially-defined function which can be mixed with others to inherit their behavior.") + +(documentation: /.mixin + "Given a mixin, produces a normal function." + [(mixin f)]) + +(documentation: /.nothing + "A mixin that does nothing and just delegates work to the next mixin.") + +(documentation: /.with + "Produces a new mixin, where the behavior of the child can make use of the behavior of the parent." + [(with parent child)]) + +(documentation: /.advice + "Only apply then mixin when the input meets some criterion." + [(advice when then)]) + +(documentation: /.before + "Executes an action before doing the main work." + [(before monad action)]) + +(documentation: /.after + "Executes an action after doing the main work." + [(after monad action)]) + +(documentation: /.Recursive + "An indirectly recursive function.") + +(documentation: /.of_recursive + "Transform an indirectly recursive function into a mixin." + [(of_recursive recursive)]) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..Mixin + ..mixin + ..nothing + ..with + ..advice + ..before + ..after + ..Recursive + ..of_recursive + ($.default /.monoid)] + [])) diff --git a/stdlib/source/documentation/lux/control/function/mutual.lux b/stdlib/source/documentation/lux/control/function/mutual.lux new file mode 100644 index 000000000..9dd7588b7 --- /dev/null +++ b/stdlib/source/documentation/lux/control/function/mutual.lux @@ -0,0 +1,50 @@ +(.module: + [library + [lux (#- let def:) + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(documentation: /.let + "Locally-defined mutually-recursive functions." + [(let [(even? number) + (-> Nat Bit) + (case number + 0 true + _ (odd? (-- number))) + + (odd? number) + (-> Nat Bit) + (case number + 0 false + _ (even? (-- number)))] + (and (even? 4) + (odd? 5)))]) + +(documentation: /.def: + "Globally-defined mutually-recursive functions." + [(def: + [.public (even? number) + (-> Nat Bit) + (case number + 0 true + _ (odd? (-- number)))] + + [.public (odd? number) + (-> Nat Bit) + (case number + 0 false + _ (even? (-- number)))])]) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..let + ..def:] + [])) diff --git a/stdlib/source/documentation/lux/control/io.lux b/stdlib/source/documentation/lux/control/io.lux index 81cf08740..085a70314 100644 --- a/stdlib/source/documentation/lux/control/io.lux +++ b/stdlib/source/documentation/lux/control/io.lux @@ -26,7 +26,7 @@ (.def: .public documentation (.List $.Module) ($.module /._ - "" + "A method for abstracting I/O and effectful computations to make it safe while writing pure functional code." [..IO ..io ..run! diff --git a/stdlib/source/documentation/lux/control/parser.lux b/stdlib/source/documentation/lux/control/parser.lux new file mode 100644 index 000000000..081c5a792 --- /dev/null +++ b/stdlib/source/documentation/lux/control/parser.lux @@ -0,0 +1,180 @@ +(.module: + [library + [lux (#- or and not) + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]] + ["." / #_ + ["#." analysis] + ["#." binary] + ["#." cli] + ["#." code] + ["#." environment] + ... ["#." json] + ... ["#." synthesis] + ... ["#." text] + ... ["#." tree] + ... ["#." type] + ... ["#." xml] + ]) + +(documentation: /.Parser + "A generic parser.") + +(documentation: /.assertion + "Fails with the given message if the test is #0." + [(assertion message test)]) + +(documentation: /.maybe + "Optionality combinator." + [(maybe parser)]) + +(documentation: /.result + (format "Executes the parser on the input." + \n "Does not verify that all of the input has been consumed by the parser." + \n "Returns both the parser's output, and a value that represents the remaining input.") + [(result parser input)]) + +(documentation: /.and + "Sequencing combinator." + [(and first second)]) + +(documentation: /.or + "Heterogeneous alternative combinator." + [(or left right)]) + +(documentation: /.either + "Homogeneous alternative combinator." + [(either this that)]) + +(documentation: /.some + "0-or-more combinator." + [(some parser)]) + +(documentation: /.many + "1-or-more combinator." + [(many parser)]) + +(documentation: /.exactly + "Parse exactly N times." + [(exactly amount parser)]) + +(documentation: /.at_least + "Parse at least N times." + [(at_least amount parser)]) + +(documentation: /.at_most + "Parse at most N times." + [(at_most amount parser)]) + +(documentation: /.between + "" + [(between minimum additional parser)]) + +(documentation: /.separated_by + "Parses instances of 'parser' that are separated by instances of 'separator'." + [(separated_by separator parser)]) + +(documentation: /.not + "Only succeeds when the underlying parser fails." + [(not parser)]) + +(documentation: /.failure + "Always fail with this 'message'." + [(failure message)]) + +(documentation: /.lifted + "Lift a potentially failed computation into a parser." + [(lifted operation)]) + +(documentation: /.else + "If the given parser fails, returns the default value." + [(else value parser)]) + +(documentation: /.remaining + "Yield the remaining input (without consuming it).") + +(documentation: /.rec + "Combinator for recursive parsers." + [(rec parser)]) + +(documentation: /.after + "Run the parser after another one (whose output is ignored)." + [(after param subject)]) + +(documentation: /.before + "Run the parser before another one (whose output is ignored)." + [(before param subject)]) + +(documentation: /.only + "Only succeed when the parser's output passes a test." + [(only test parser)]) + +(documentation: /.parses? + "Ignore a parser's output and just verify that it succeeds." + [(parses? parser)]) + +(documentation: /.parses + "Ignore a parser's output and just execute it." + [(parses parser)]) + +(documentation: /.speculative + (format "Executes a parser, without actually consuming the input." + \n "That way, the same input can be consumed again by another parser.") + [(speculative parser)]) + +(documentation: /.codec + "Decode the output of a parser using a codec." + [(codec codec parser)]) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..Parser + ..assertion + ..maybe + ..result + ..and + ..or + ..either + ..some + ..many + ..exactly + ..at_least + ..at_most + ..between + ..separated_by + ..not + ..failure + ..lifted + ..else + ..remaining + ..rec + ..after + ..before + ..only + ..parses? + ..parses + ..speculative + ..codec + ($.default /.functor) + ($.default /.apply) + ($.default /.monad)] + [/analysis.documentation + /binary.documentation + /cli.documentation + /code.documentation + /environment.documentation + ... /json.documentation + ... /synthesis.documentation + ... /text.documentation + ... /tree.documentation + ... /type.documentation + ... /xml.documentation + ])) diff --git a/stdlib/source/documentation/lux/control/parser/analysis.lux b/stdlib/source/documentation/lux/control/parser/analysis.lux new file mode 100644 index 000000000..1f66be4bf --- /dev/null +++ b/stdlib/source/documentation/lux/control/parser/analysis.lux @@ -0,0 +1,71 @@ +(.module: + [library + [lux (#- nat int rev local) + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(documentation: /.Parser + "A parser for Lux code analysis nodes.") + +(documentation: /.result + "Executes a parser and makes sure no inputs go unconsumed." + [(result parser input)]) + +(documentation: /.any + "Matches any value, without discrimination.") + +(documentation: /.end! + "Ensures there are no more inputs.") + +(documentation: /.end? + "Checks whether there are no more inputs.") + +(template [<query> <assertion>] + [(`` (as_is (`` (documentation: <query> + (format "Queries for a " (~~ (template.text [<query>])) " value."))) + (`` (documentation: <assertion> + (format "Assert a specific " (~~ (template.text [<query>])) " value.")))))] + + [/.bit /.bit!] + [/.nat /.nat!] + [/.int /.int!] + [/.rev /.rev!] + [/.frac /.frac!] + [/.text /.text!] + [/.local /.local!] + [/.foreign /.foreign!] + [/.constant /.constant!] + ) + +(documentation: /.tuple + "Parses only within the context of a tuple's contents." + [(tuple parser)]) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..Parser + ..result + ..any + ..end! + ..end? + ..bit ..bit! + ..nat ..nat! + ..int ..int! + ..rev ..rev! + ..frac ..frac! + ..text ..text! + ..local ..local! + ..foreign ..foreign! + ..constant ..constant! + ..tuple + ($.default /.cannot_parse) + ($.default /.unconsumed_input)] + [])) diff --git a/stdlib/source/documentation/lux/control/parser/binary.lux b/stdlib/source/documentation/lux/control/parser/binary.lux new file mode 100644 index 000000000..c20d3b0a7 --- /dev/null +++ b/stdlib/source/documentation/lux/control/parser/binary.lux @@ -0,0 +1,139 @@ +(.module: + [library + [lux (#- list) + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(documentation: /.Offset + "An offset for reading within binary data.") + +(documentation: /.Parser + "A parser for raw binary data.") + +(documentation: /.result + "Runs a parser and checks that all the binary data was read by it." + [(result parser input)]) + +(documentation: /.end? + "Checks whether there is no more data to read.") + +(documentation: /.offset + "The current offset (i.e. how much data has been read).") + +(documentation: /.remaining + "How much of the data remains to be read.") + +(documentation: /.Size + "The size of a chunk of data within a binary array.") + +(documentation: /.rec + "Tie the knot for a recursive parser.") + +(documentation: /.any + "Does no parsing, and just returns a dummy value.") + +(documentation: /.segment + "Parses a chunk of data of a given size." + [(segment size)]) + +(template [<size> <name>] + [(documentation: <name> + (format "Parses a block of data prefixed with a size that is " (%.nat <size>) " bytes long."))] + + [08 /.binary/8] + [16 /.binary/16] + [32 /.binary/32] + [64 /.binary/64] + ) + +(template [<size> <name>] + [(documentation: <name> + (format "Parses a block of (UTF-8 encoded) text prefixed with a size that is " (%.nat <size>) " bytes long."))] + + [08 /.utf8/8] + [16 /.utf8/16] + [32 /.utf8/32] + [64 /.utf8/64] + ) + +(template [<size> <name>] + [(documentation: <name> + (format "Parses a row of values prefixed with a size that is " (%.nat <size>) " bytes long."))] + + [08 /.row/8] + [16 /.row/16] + [32 /.row/32] + [64 /.row/64] + ) + +(documentation: /.list + "Parses an arbitrarily long list of values." + [(list value)]) + +(documentation: /.set + "" + [(set hash value)]) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..Offset + ..Parser + ..result + ..end? + ..offset + ..remaining + ..Size + ..rec + ..any + ..segment + + ..binary/8 + ..binary/16 + ..binary/32 + ..binary/64 + + ..utf8/8 + ..utf8/16 + ..utf8/32 + ..utf8/64 + + ..row/8 + ..row/16 + ..row/32 + ..row/64 + + ..list + ..set + ($.default /.binary_was_not_fully_read) + ($.default /.size/8) + ($.default /.size/16) + ($.default /.size/32) + ($.default /.size/64) + ($.default /.bits/8) + ($.default /.bits/16) + ($.default /.bits/32) + ($.default /.bits/64) + ($.default /.nat) + ($.default /.int) + ($.default /.rev) + ($.default /.frac) + ($.default /.invalid_tag) + ($.default /.or) + ($.default /.not_a_bit) + ($.default /.bit) + ($.default /.text) + ($.default /.maybe) + ($.default /.set_elements_are_not_unique) + ($.default /.name) + ($.default /.type) + ($.default /.location) + ($.default /.code)] + [])) diff --git a/stdlib/source/documentation/lux/control/parser/cli.lux b/stdlib/source/documentation/lux/control/parser/cli.lux new file mode 100644 index 000000000..ecb2b4cb7 --- /dev/null +++ b/stdlib/source/documentation/lux/control/parser/cli.lux @@ -0,0 +1,59 @@ +(.module: + [library + [lux #* + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(documentation: /.Parser + "A command-line interface parser.") + +(documentation: /.result + "Executes the parser and verifies that all inputs are processed." + [(result parser inputs)]) + +(documentation: /.any + "Just returns the next input without applying any logic.") + +(documentation: /.parse + "Parses the next input with a parsing function." + [(parse parser)]) + +(documentation: /.this + "Checks that a token is in the inputs." + [(this reference)]) + +(documentation: /.somewhere + "Given a parser, tries to parse it somewhere in the inputs (i.e. not necessarily parsing the immediate inputs)." + [(somewhere cli)]) + +(documentation: /.end + "Ensures there are no more inputs.") + +(documentation: /.named + "Parses a named parameter and yields its value." + [(named name value)]) + +(documentation: /.parameter + "Parses a parameter that can have either a short or a long name." + [(parameter [short long] value)]) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..Parser + ..result + ..any + ..parse + ..this + ..somewhere + ..end + ..named + ..parameter] + [])) diff --git a/stdlib/source/documentation/lux/control/parser/code.lux b/stdlib/source/documentation/lux/control/parser/code.lux new file mode 100644 index 000000000..aa7e91442 --- /dev/null +++ b/stdlib/source/documentation/lux/control/parser/code.lux @@ -0,0 +1,113 @@ +(.module: + [library + [lux (#- nat int rev local) + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(documentation: /.Parser + "A Lux code parser.") + +(documentation: /.any + "Yields the next input without applying any logic.") + +(template [<query> <check>] + [(`` (documentation: <query> + (format "Parses the next " (~~ (template.text [<query>])) " input."))) + (`` (documentation: <check> + (format "Checks for a specific " (~~ (template.text [<query>])) " input.")))] + + [/.bit /.bit!] + [/.nat /.nat!] + [/.int /.int!] + [/.rev /.rev!] + [/.frac /.frac!] + [/.text /.text!] + [/.identifier /.identifier!] + [/.tag /.tag!] + ) + +(documentation: /.this! + "Ensures the given Code is the next input." + [(this! code)]) + +(template [<query> <check> <desc>] + [(documentation: <query> + (format "Parse a local " <desc> " (a " <desc> " that has no module prefix).")) + (documentation: <check> + (format "Checks for a specific local " <desc> " (a " <desc> " that has no module prefix)."))] + + [/.local_identifier /.local_identifier! "local identifier"] + [ /.local_tag /.local_tag! "local tag"] + ) + +(template [<name>] + [(`` (documentation: <name> + (format "Parses the contents of a " (~~ (template.text [<name>])) ".")))] + + [/.form] + [/.tuple] + ) + +(documentation: /.record + "Parses the contents of a record.") + +(documentation: /.end! + "Verifies there are no more inputs.") + +(documentation: /.end? + "Checks whether there are no more inputs.") + +(documentation: /.result + "Executes a parser against a stream of code, and verifies all the inputs are consumed." + [(result parser inputs)]) + +(documentation: /.local + "Runs parser against the given list of inputs." + [(local inputs parser)]) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..Parser + ..any + + ..bit + ..bit! + ..nat + ..nat! + ..int + ..int! + ..rev + ..rev! + ..frac + ..frac! + ..text + ..text! + ..identifier + ..identifier! + ..tag + ..tag! + + ..this! + + ..local_identifier + ..local_identifier! + ..local_tag + ..local_tag! + + ..form + ..tuple + + ..record + ..end! + ..end? + ..result + ..local] + [])) diff --git a/stdlib/source/documentation/lux/control/parser/environment.lux b/stdlib/source/documentation/lux/control/parser/environment.lux new file mode 100644 index 000000000..f4961a0d4 --- /dev/null +++ b/stdlib/source/documentation/lux/control/parser/environment.lux @@ -0,0 +1,45 @@ +(.module: + [library + [lux #* + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(documentation: /.Property + "A property in the environment.") + +(documentation: /.Environment + "An abstraction for environment variables of a program.") + +(documentation: /.Parser + "A parser of environment variables of a program.") + +(documentation: /.empty + "An empty environment.") + +(documentation: /.property + "" + [(property name)]) + +(documentation: /.result + (format "Executes a parser against the given environment variables." + \n "Does not check whether all environment variables were parsed, since they're usually an open set.") + [(result parser environment)]) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..Property + ..Environment + ..Parser + ..empty + ..property + ..result + ($.default /.unknown_property)] + [])) diff --git a/stdlib/source/documentation/lux/control/pipe.lux b/stdlib/source/documentation/lux/control/pipe.lux new file mode 100644 index 000000000..f18415290 --- /dev/null +++ b/stdlib/source/documentation/lux/control/pipe.lux @@ -0,0 +1,117 @@ +(.module: + [library + [lux (#- if loop) + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(documentation: /.new> + "Ignores the piped argument, and begins a new pipe." + [(n.= 1 + (|> 20 + (n.* 3) + (n.+ 4) + (new> 0 [++])))]) + +(documentation: /.let> + "Gives a name to the piped-argument, within the given expression." + [(n.= 10 + (|> 5 + (let> x (n.+ x x))))]) + +(documentation: /.cond> + (format "Branching for pipes." + \n "Both the tests and the bodies are piped-code, and must be given inside a tuple.") + [(|> +5 + (cond> [i.even?] [(i.* +2)] + [i.odd?] [(i.* +3)] + [(new> -1 [])]))]) + +(documentation: /.if> + "If-branching." + [(same? (if (n.even? sample) + "even" + "odd") + (|> sample + (if> [n.even?] + [(new> "even" [])] + [(new> "odd" [])])))]) + +(documentation: /.when> + "Only execute the body when the test passes." + [(same? (if (n.even? sample) + (n.* 2 sample) + sample) + (|> sample + (when> [n.even?] + [(n.* 2)])))]) + +(documentation: /.loop> + (format "Loops for pipes." + \n "Both the testing and calculating steps are pipes and must be given inside tuples.") + [(|> +1 + (loop> [(i.< +10)] + [++]))]) + +(documentation: /.do> + (format "Monadic pipes." + \n "Each steps in the monadic computation is a pipe and must be given inside a tuple.") + [(|> +5 + (do> identity.monad + [(i.* +3)] + [(i.+ +4)] + [++]))]) + +(documentation: /.exec> + (format "Non-updating pipes." + \n "Will generate piped computations, but their results will not be used in the larger scope.") + [(|> +5 + (exec> [.nat %n log!]) + (i.* +10))]) + +(documentation: /.tuple> + (format "Parallel branching for pipes." + \n "Allows to run multiple pipelines for a value and gives you a tuple of the outputs.") + [(|> +5 + (tuple> [(i.* +10)] + [-- (i./ +2)] + [i\encode])) + "=>" + [+50 +2 "+5"]]) + +(documentation: /.case> + (format "Pattern-matching for pipes." + \n "The bodies of each branch are NOT pipes; just regular values.") + [(|> +5 + (case> +0 "zero" + +1 "one" + +2 "two" + +3 "three" + +4 "four" + +5 "five" + +6 "six" + +7 "seven" + +8 "eight" + +9 "nine" + _ "???"))]) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..new> + ..let> + ..cond> + ..if> + ..when> + ..loop> + ..do> + ..exec> + ..tuple> + ..case>] + [])) diff --git a/stdlib/source/documentation/lux/control/reader.lux b/stdlib/source/documentation/lux/control/reader.lux new file mode 100644 index 000000000..959c44217 --- /dev/null +++ b/stdlib/source/documentation/lux/control/reader.lux @@ -0,0 +1,47 @@ +(.module: + [library + [lux (#- local) + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(documentation: /.Reader + "Computations that have access to some environmental value.") + +(documentation: /.read + "Get the environment.") + +(documentation: /.local + "Run computation with a locally-modified environment." + [(local change proc)]) + +(documentation: /.result + "Executes the reader against the given environment." + [(result env proc)]) + +(documentation: /.with + "Monad transformer for Reader." + [(with monad)]) + +(documentation: /.lifted + "Lift monadic values to the Reader wrapper.") + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..Reader + ..read + ..local + ..result + ..with + ..lifted + ($.default /.functor) + ($.default /.apply) + ($.default /.monad)] + [])) diff --git a/stdlib/source/documentation/lux/control/region.lux b/stdlib/source/documentation/lux/control/region.lux new file mode 100644 index 000000000..08e8177b9 --- /dev/null +++ b/stdlib/source/documentation/lux/control/region.lux @@ -0,0 +1,51 @@ +(.module: + [library + [lux (#- if loop) + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(documentation: /.Region + (format "A region where resources may be be claimed and where a side-effecting computation may be performed." + \n "Every resource is paired with a function that knows how to clean/reclaim it, to make sure there are no leaks.")) + +(documentation: /.run! + "Executes a region-based computation, with a side-effect determined by the monad." + [(run! monad computation)]) + +(documentation: /.acquire! + "Acquire a resource while pairing it a function that knows how to reclaim it." + [(acquire! monad cleaner value)]) + +(documentation: /.failure + "Immediately fail with this 'message'." + [(failure monad error)]) + +(documentation: /.except + "Fail by throwing/raising an exception." + [(except monad exception message)]) + +(documentation: /.lifted + "Lift an effectful computation into a region-based computation." + [(lifted monad operation)]) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..Region + ..run! + ..acquire! + ..failure + ..except + ..lifted + ($.default /.clean_up_error) + ($.default /.functor) + ($.default /.apply) + ($.default /.monad)] + [])) diff --git a/stdlib/source/documentation/lux/control/remember.lux b/stdlib/source/documentation/lux/control/remember.lux new file mode 100644 index 000000000..c17fdf3cc --- /dev/null +++ b/stdlib/source/documentation/lux/control/remember.lux @@ -0,0 +1,38 @@ +(.module: + [library + [lux #* + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(template [<name> <type>] + [(`` (documentation: <name> + (format "A" <type> " message with an expiration date." + \n "Can have an optional piece of code to focus on.") + [((~~ (template.identifier [<name>])) + "2022-04-01" + "Do this, that and the other.")] + [((~~ (template.identifier [<name>])) + "2022-04-01" + "Improve the performace." + (some (complicated (computation 123))))]))] + + [/.remember ""] + [/.to_do " TODO"] + [/.fix_me " FIXME"] + ) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..remember + ..to_do + ..fix_me + ($.default /.must_remember)] + [])) diff --git a/stdlib/source/documentation/lux/control/security.lux b/stdlib/source/documentation/lux/control/security.lux new file mode 100644 index 000000000..ac39298dd --- /dev/null +++ b/stdlib/source/documentation/lux/control/security.lux @@ -0,0 +1,18 @@ +(.module: + [library + [lux #* + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]] + [collection + ["." list]]]]] + ["." / #_ + ["#." capability] + ["#." policy]]) + +(.def: .public documentation + (.List $.Module) + (list.together + (list /policy.documentation + /capability.documentation))) diff --git a/stdlib/source/documentation/lux/control/security/capability.lux b/stdlib/source/documentation/lux/control/security/capability.lux new file mode 100644 index 000000000..fb43184d8 --- /dev/null +++ b/stdlib/source/documentation/lux/control/security/capability.lux @@ -0,0 +1,44 @@ +(.module: + [library + [lux #* + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(documentation: /.Capability + (format "Represents the capability to perform an operation." + \n "This operation is assumed to have security implications.")) + +(documentation: /.use + "Applies a capability against its required input." + [(use capability input)]) + +(documentation: /.capability: + "Defines a capability as a unique type, and a constructor for instances." + [(capability: (Can_Duplicate a) + (can_duplicate a [a a])) + + (let [capability (can_duplicate + (function (_ value) + [value value])) + [left right] (..use capability 123)] + (same? left right))]) + +(documentation: /.async + "Converts a synchronous I/O-based capability into an asynchronous capability." + [(async capability)]) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..Capability + ..use + ..capability: + ..async] + [])) diff --git a/stdlib/source/documentation/lux/control/security/policy.lux b/stdlib/source/documentation/lux/control/security/policy.lux new file mode 100644 index 000000000..9d9cb655d --- /dev/null +++ b/stdlib/source/documentation/lux/control/security/policy.lux @@ -0,0 +1,89 @@ +(.module: + [library + [lux #* + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(documentation: /.Policy + "A security policy encoded as the means to 'upgrade' or 'downgrade' in a secure context.") + +(documentation: /.Can_Upgrade + "Represents the capacity to 'upgrade' a value.") + +(documentation: /.Can_Downgrade + "Represents the capacity to 'downgrade' a value.") + +(documentation: /.Privilege + "Represents the privilege to both 'upgrade' and 'downgrade' a value.") + +(documentation: /.Delegation + "Represents the act of delegating policy capacities.") + +(documentation: /.delegation + "Delegating policy capacities." + [(delegation downgrade upgrade)]) + +(documentation: /.Context + "A computational context with an associated policy privilege.") + +(documentation: /.with_policy + "Activates a security context with the priviledge to enforce it's policy." + [(type: Password + (Private Text)) + + (interface: (Policy %) + (: (-> Text (Password %)) + password) + (: (-> (Password %) Text) + unsafe)) + + (def: (policy _) + (Ex [%] (-> Any (Policy %))) + (with_policy + (: (Context Privacy Policy) + (function (_ (^open "%::.")) + (implementation + (def: (password value) + (%::can_upgrade value)) + (def: (unsafe password) + (%::can_downgrade password)))))))] + [(with_policy context)]) + +(documentation: /.Privacy + (format "A security context for privacy." + \n "Private data is data which cannot be allowed to leak outside of the programmed.")) + +(documentation: /.Safety + (format "A security context for safety." + \n "Safe data is data coming from outside the program which can be trusted to be properly formatted and lacking injections.")) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..Policy + ..Can_Upgrade + ..Can_Downgrade + ..Privilege + ..Delegation + ..delegation + ..Context + ..with_policy + ..Privacy + ..Safety + ($.default /.functor) + ($.default /.apply) + ($.default /.monad) + ($.default /.Private) + ($.default /.Can_Conceal) + ($.default /.Can_Reveal) + ($.default /.Safe) + ($.default /.Can_Trust) + ($.default /.Can_Distrust)] + [])) diff --git a/stdlib/source/documentation/lux/control/state.lux b/stdlib/source/documentation/lux/control/state.lux new file mode 100644 index 000000000..99be4d130 --- /dev/null +++ b/stdlib/source/documentation/lux/control/state.lux @@ -0,0 +1,82 @@ +(.module: + [library + [lux (#- local) + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(documentation: /.State + "Stateful computations.") + +(documentation: /.get + "Read the current state.") + +(documentation: /.put + "Set the new state." + [(put new_state)]) + +(documentation: /.update + "Compute the new state." + [(update change)]) + +(documentation: /.use + "Run a function on the current state." + [(use user)]) + +(documentation: /.local + "Run the computation with a locally-modified state." + [(local change action)]) + +(documentation: /.result + "Run a stateful computation." + [(result state action)]) + +(documentation: /.while + "A stateful while loop." + [(while condition body)]) + +(documentation: /.do_while + "A stateful do-while loop." + [(do_while condition body)]) + +(documentation: /.+State + "Stateful computations decorated by a monad.") + +(documentation: /.result' + "Execute a stateful computation decorated by a monad." + [(result' state action)]) + +(documentation: /.with + "A monad transformer to create composite stateful computations." + [(with monad)]) + +(documentation: /.lifted + "Lift monadic values to the +State wrapper." + [(lifted monad ma)]) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..State + ..get + ..put + ..update + ..use + ..local + ..result + ..while + ..do_while + ..+State + ..result' + ..with + ..lifted + ($.default /.functor) + ($.default /.apply) + ($.default /.monad)] + [])) diff --git a/stdlib/source/documentation/lux/control/thread.lux b/stdlib/source/documentation/lux/control/thread.lux new file mode 100644 index 000000000..cc3134d2f --- /dev/null +++ b/stdlib/source/documentation/lux/control/thread.lux @@ -0,0 +1,57 @@ +(.module: + [library + [lux (#- local) + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(documentation: /.Thread + "An imperative process with access to mutable values.") + +(documentation: /.Box + "A mutable box holding a value.") + +(documentation: /.box + "A brand-new box initialized to the given value." + [(box init)]) + +(documentation: /.read! + "Reads the current value in the box." + [(read! box)]) + +(documentation: /.write! + "Mutates the value in the box." + [(write! value box)]) + +(documentation: /.result + "Executes the imperative thread in a self-contained way." + [(result thread)]) + +(documentation: /.io + "Transforms the imperative thread into an I/O computation.") + +(documentation: /.update! + "Update a box's value by applying a function to it." + [(update! f box)]) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..Thread + ..Box + ..box + ..read! + ..write! + ..result + ..io + ..update! + ($.default /.functor) + ($.default /.apply) + ($.default /.monad)] + [])) diff --git a/stdlib/source/documentation/lux/control/try.lux b/stdlib/source/documentation/lux/control/try.lux new file mode 100644 index 000000000..7b226c132 --- /dev/null +++ b/stdlib/source/documentation/lux/control/try.lux @@ -0,0 +1,62 @@ +(.module: + [library + [lux (#- local) + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(documentation: /.Try + "A computation that can fail with an error message.") + +(documentation: /.with + "Enhances a monad with error-handling functionality." + [(with monad)]) + +(documentation: /.lifted + "Wraps a monadic value with error-handling machinery." + [(lifted monad)]) + +(documentation: /.trusted + (format "Assumes a Try value succeeded, and yields its value." + \n "If it didn't, raises the error as a runtime error." + \n "WARNING: Use with caution.") + [(trusted try)]) + +(documentation: /.maybe + "" + [(maybe try)]) + +(documentation: /.of_maybe + "" + [(of_maybe maybe)]) + +(documentation: /.else + (format "Allows you to provide a default value that will be used" + \n "if a (Try x) value turns out to be #Failure." + \n "Note: the expression for the default value will not be computed if the base computation succeeds.") + [(= "bar" + (else "foo" (#..Success "bar")))] + [(= "foo" + (else "foo" (#..Failure "KABOOM!")))]) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..Try + ..with + ..lifted + ..trusted + ..maybe + ..of_maybe + ..else + ($.default /.functor) + ($.default /.apply) + ($.default /.monad) + ($.default /.equivalence)] + [])) diff --git a/stdlib/source/documentation/lux/control/writer.lux b/stdlib/source/documentation/lux/control/writer.lux new file mode 100644 index 000000000..99cbe0463 --- /dev/null +++ b/stdlib/source/documentation/lux/control/writer.lux @@ -0,0 +1,39 @@ +(.module: + [library + [lux (#- local) + ["$" documentation (#+ documentation:)] + [data + [text (#+ \n) + ["%" format (#+ format)]]] + [macro + ["." template]]]] + [\\library + ["." /]]) + +(documentation: /.Writer + "Represents a value with an associated 'log' to record arbitrary information.") + +(documentation: /.write + "Write a value to the log." + [(write message)]) + +(documentation: /.with + "Enhances a monad with Writer functionality." + [(with monoid monad)]) + +(documentation: /.lifted + "Wraps a monadic value with Writer machinery." + [(lifted monoid monad)]) + +(.def: .public documentation + (.List $.Module) + ($.module /._ + "" + [..Writer + ..write + ..with + ..lifted + ($.default /.functor) + ($.default /.apply) + ($.default /.monad)] + [])) |