aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/documentation
diff options
context:
space:
mode:
authorEduardo Julian2022-06-26 18:37:05 -0400
committerEduardo Julian2022-06-26 18:37:05 -0400
commit9f6505491e8a5c8a159ce094fe0af6f4fef0c5cf (patch)
treed497c163e477406a388460eedea80fdd6ee9748a /stdlib/source/documentation
parent3053fd79bc6ae42415298ee056a268dc2c9b690c (diff)
Re-named "format/lux/data/binary.Writer" to "Format".
Diffstat (limited to 'stdlib/source/documentation')
-rw-r--r--stdlib/source/documentation/lux.lux1712
-rw-r--r--stdlib/source/documentation/lux/abstract.lux4
-rw-r--r--stdlib/source/documentation/lux/abstract/apply.lux6
-rw-r--r--stdlib/source/documentation/lux/abstract/codec.lux6
-rw-r--r--stdlib/source/documentation/lux/abstract/comonad.lux10
-rw-r--r--stdlib/source/documentation/lux/abstract/comonad/cofree.lux16
-rw-r--r--stdlib/source/documentation/lux/abstract/comonad/free.lux17
-rw-r--r--stdlib/source/documentation/lux/abstract/enum.lux6
-rw-r--r--stdlib/source/documentation/lux/abstract/equivalence.lux6
-rw-r--r--stdlib/source/documentation/lux/abstract/functor.lux23
-rw-r--r--stdlib/source/documentation/lux/abstract/functor/contravariant.lux4
-rw-r--r--stdlib/source/documentation/lux/abstract/hash.lux11
-rw-r--r--stdlib/source/documentation/lux/abstract/interval.lux57
-rw-r--r--stdlib/source/documentation/lux/abstract/mix.lux17
-rw-r--r--stdlib/source/documentation/lux/abstract/monad.lux70
-rw-r--r--stdlib/source/documentation/lux/abstract/monad/free.lux13
-rw-r--r--stdlib/source/documentation/lux/abstract/monoid.lux13
-rw-r--r--stdlib/source/documentation/lux/abstract/order.lux52
-rw-r--r--stdlib/source/documentation/lux/abstract/predicate.lux56
-rw-r--r--stdlib/source/documentation/lux/control/concatenative.lux429
-rw-r--r--stdlib/source/documentation/lux/control/concurrency.lux2
-rw-r--r--stdlib/source/documentation/lux/control/concurrency/actor.lux89
-rw-r--r--stdlib/source/documentation/lux/control/concurrency/async.lux123
-rw-r--r--stdlib/source/documentation/lux/control/concurrency/atom.lux42
-rw-r--r--stdlib/source/documentation/lux/control/concurrency/frp.lux74
-rw-r--r--stdlib/source/documentation/lux/control/concurrency/semaphore.lux81
-rw-r--r--stdlib/source/documentation/lux/control/concurrency/stm.lux60
-rw-r--r--stdlib/source/documentation/lux/control/concurrency/thread.lux17
-rw-r--r--stdlib/source/documentation/lux/control/continuation.lux61
-rw-r--r--stdlib/source/documentation/lux/control/exception.lux104
-rw-r--r--stdlib/source/documentation/lux/control/function.lux57
-rw-r--r--stdlib/source/documentation/lux/control/function/contract.lux38
-rw-r--r--stdlib/source/documentation/lux/control/function/memo.lux37
-rw-r--r--stdlib/source/documentation/lux/control/function/mixin.lux69
-rw-r--r--stdlib/source/documentation/lux/control/function/mutual.lux65
-rw-r--r--stdlib/source/documentation/lux/control/io.lux35
-rw-r--r--stdlib/source/documentation/lux/control/lazy.lux24
-rw-r--r--stdlib/source/documentation/lux/control/maybe.lux66
-rw-r--r--stdlib/source/documentation/lux/control/parser.lux209
-rw-r--r--stdlib/source/documentation/lux/control/pipe.lux183
-rw-r--r--stdlib/source/documentation/lux/control/reader.lux52
-rw-r--r--stdlib/source/documentation/lux/control/region.lux60
-rw-r--r--stdlib/source/documentation/lux/control/remember.lux61
-rw-r--r--stdlib/source/documentation/lux/control/security.lux2
-rw-r--r--stdlib/source/documentation/lux/control/state.lux101
-rw-r--r--stdlib/source/documentation/lux/control/thread.lux66
-rw-r--r--stdlib/source/documentation/lux/control/try.lux81
-rw-r--r--stdlib/source/documentation/lux/control/writer.lux40
-rw-r--r--stdlib/source/documentation/lux/data/format/binary.lux8
-rw-r--r--stdlib/source/documentation/lux/data/format/tar.lux2
50 files changed, 2066 insertions, 2371 deletions
diff --git a/stdlib/source/documentation/lux.lux b/stdlib/source/documentation/lux.lux
index 0bf71c4ad..0b0e815a7 100644
--- a/stdlib/source/documentation/lux.lux
+++ b/stdlib/source/documentation/lux.lux
@@ -2,7 +2,7 @@
[library
[lux
[program (.only program:)]
- ["$" documentation (.only documentation)]
+ ["$" documentation]
["[0]" debug]
[control
["[0]" io]]
@@ -37,879 +37,879 @@
["[1][0]" type]
["[1][0]" world]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [(documentation /.prelude
- (format "The name of the prelude module"
- \n "Value: " (%.text /.prelude)))
+(.`` (.def .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [($.documentation /.prelude
+ (format "The name of the prelude module"
+ \n "Value: " (%.text /.prelude)))
- (documentation /.Any
- (format "The type of things whose type is irrelevant."
- \n "It can be used to write functions or data-structures that can take, or return, anything."))
+ ($.documentation /.Any
+ (format "The type of things whose type is irrelevant."
+ \n "It can be used to write functions or data-structures that can take, or return, anything."))
- (documentation /.Nothing
- (format "The type of things whose type is undefined."
- \n "Useful for expressions that cause errors or other 'extraordinary' conditions."))
+ ($.documentation /.Nothing
+ (format "The type of things whose type is undefined."
+ \n "Useful for expressions that cause errors or other 'extraordinary' conditions."))
- (documentation (/.List item)
- "A potentially empty list of values.")
+ ($.documentation (/.List item)
+ "A potentially empty list of values.")
- (documentation /.Bit
- "Your standard, run-of-the-mill boolean values (as #0 or #1 bits).")
+ ($.documentation /.Bit
+ "Your standard, run-of-the-mill boolean values (as #0 or #1 bits).")
- (documentation (/.I64 kind)
- "64-bit integers without any semantics.")
+ ($.documentation (/.I64 kind)
+ "64-bit integers without any semantics.")
- (documentation /.Nat
- (format "Natural numbers (unsigned integers)."
- \n "They start at zero (0) and extend in the positive direction."))
+ ($.documentation /.Nat
+ (format "Natural numbers (unsigned integers)."
+ \n "They start at zero (0) and extend in the positive direction."))
- (documentation /.Int
- "Your standard, run-of-the-mill integer numbers.")
+ ($.documentation /.Int
+ "Your standard, run-of-the-mill integer numbers.")
- (documentation /.Rev
- (format "Fractional numbers that live in the interval [0,1)."
- \n "Useful for probability, and other domains that work within that interval."))
+ ($.documentation /.Rev
+ (format "Fractional numbers that live in the interval [0,1)."
+ \n "Useful for probability, and other domains that work within that interval."))
- (documentation /.Frac
- "Your standard, run-of-the-mill floating-point (fractional) numbers.")
+ ($.documentation /.Frac
+ "Your standard, run-of-the-mill floating-point (fractional) numbers.")
- (documentation /.Text
- "Your standard, run-of-the-mill string values.")
+ ($.documentation /.Text
+ "Your standard, run-of-the-mill string values.")
- (documentation /.Symbol
- (format "A name for a Lux definition."
- \n "It includes the module of provenance."))
+ ($.documentation /.Symbol
+ (format "A name for a Lux definition."
+ \n "It includes the module of provenance."))
- (documentation (/.Maybe value)
- "A potentially missing value.")
+ ($.documentation (/.Maybe value)
+ "A potentially missing value.")
- (documentation /.Type
- "This type represents the data-structures that are used to specify types themselves.")
+ ($.documentation /.Type
+ "This type represents the data-structures that are used to specify types themselves.")
- (documentation /.Location
- "Locations are for specifying the location of Code nodes in Lux files during compilation.")
-
- (documentation (/.Ann meta_data datum)
- "The type of things that can be annotated with meta-data of arbitrary types.")
-
- (documentation /.Code
- "The type of Code nodes for Lux syntax.")
-
- (documentation /.private
- "The export policy for private/local definitions.")
-
- (documentation /.local
- "The export policy for private/local definitions.")
-
- (documentation /.public
- "The export policy for public/global definitions.")
-
- (documentation /.global
- "The export policy for public/global definitions.")
-
- (documentation /.Definition
- "Represents all the data associated with a definition: its type, its annotations, and its value.")
-
- (documentation /.Global
- "Represents all the data associated with a global constant.")
-
- (documentation (/.Either left right)
- "A choice between two values of different types.")
-
- (documentation /.Module
- "All the information contained within a Lux module.")
-
- (documentation /.Mode
- "A sign that shows the conditions under which the compiler is running.")
-
- (documentation /.Info
- "Information about the current version and type of compiler that is running.")
-
- (documentation /.Lux
- (format "Represents the state of the Lux compiler during a run."
- \n "It is provided to macros during their invocation, so they can access compiler data."
- \n "Caveat emptor: Avoid fiddling with it, unless you know what you're doing."))
-
- (documentation (/.Meta it)
- (format "Computations that can have access to the state of the compiler."
- \n "These computations may fail, or modify the state of the compiler."))
-
- (documentation /.Macro
- "Functions that run at compile-time and allow you to transform and extend the language in powerful ways.")
-
- (documentation /.comment
- (format "Throws away any code given to it."
- \n "Great for commenting-out code, while retaining syntax high-lighting and formatting in your text editor.")
- [(comment
- (def (this will not)
- (Be Defined)
- (because it will be (commented out))))])
-
- (documentation /.All
- "Universal quantification."
- [(All (_ a)
- (-> a a))]
- ["A name can be provided, to specify a recursive type."
- (All (List a)
- (Or Any
- [a (List a)]))])
-
- (documentation /.Ex
- "Existential quantification."
- [(Ex (_ a)
- [(Codec Text a) a])]
- ["A name can be provided, to specify a recursive type."
- (Ex (Self a)
- [(Codec Text a)
- a
- (List (Self a))])])
-
- (documentation /.->
- "Function types."
- ["This is the type of a function that takes 2 Ints and returns an Int."
- (-> Int Int Int)])
-
- (documentation /.list
- "List literals."
- [(is (List Nat)
- (list 0 1 2 3))])
-
- (documentation /.Union
- "Union types."
- [(Union Bit Nat Text)]
- [(= Nothing
- (Union))])
-
- (documentation /.Tuple
- "Tuple types."
- [(Tuple Bit Nat Text)]
- [(= Any
- (Tuple))])
-
- (documentation /.Or
- "An alias for the Union type constructor."
- [(= (Union Bit Nat Text)
- (Or Bit Nat Text))]
- [(= (Union)
- (Or))])
-
- (documentation /.And
- "An alias for the Tuple type constructor."
- [(= (Tuple Bit Nat Text)
- (And Bit Nat Text))]
- [(= (Tuple)
- (And))])
-
- (documentation /.left
- "Left-association for the application of binary functions over variadic arguments."
- [(left text#composite "Hello, " name ". How are you?")
- "=>"
- (text#composite (text#composite "Hello, " name) ". How are you?")])
-
- (documentation /.all
- "Right-association for the application of binary functions over variadic arguments."
- [(all text#composite "Hello, " name ". How are you?")
- "=>"
- (text#composite "Hello, " (text#composite name ". How are you?"))])
-
- (documentation /.if
- "Picks which expression to evaluate based on a bit test value."
- [(if #1
- "Oh, yeah!"
- "Aw hell naw!")
- "=>"
- "Oh, yeah!"]
- [(if #0
- "Oh, yeah!"
- "Aw hell naw!")
- "=>"
- "Aw hell naw!"])
-
- (documentation /.Primitive
- "Macro to treat define new primitive types."
- [(Primitive "java.lang.Object")]
- [(Primitive "java.util.List" [(Primitive "java.lang.Long")])])
-
- (documentation /.`
- (format "Hygienic quasi-quotation as a macro."
- \n "Unquote (~) and unquote-splice (~+) must also be used as forms."
- \n "All unprefixed macros will receive their parent module's prefix if imported; otherwise will receive the prefix of the module on which the quasi-quote is being used.")
- [(` (def (~ name)
- (function ((~' _) (~+ args))
- (~ body))))])
-
- (documentation /.`'
- (format "Unhygienic quasi-quotation as a macro."
- \n "Unquote (~) and unquote-splice (~+) must also be used as forms.")
- [(`' (def (~ name)
- (function (_ (~+ args))
- (~ body))))])
-
- (documentation /.'
- "Quotation as a macro."
- [(' YOLO)])
-
- (documentation /.|>
- "Piping macro."
- [(|> elems
- (list#each int#encoded)
- (interposed " ")
- (mix text#composite ""))
- "=>"
- (mix text#composite ""
- (interposed " "
- (list#each int#encoded
- elems)))])
-
- (documentation /.<|
- "Reverse piping macro."
- [(<| (mix text#composite "")
- (interposed " ")
- (list#each int#encoded)
- elems)
- "=>"
- (mix text#composite ""
- (interposed " "
- (list#each int#encoded
- elems)))])
-
- (documentation /.template
- ""
- ["By specifying a pattern (with holes), and the input data to fill those holes, repeats the pattern as many times as necessary."
- (with_template [<name> <diff>]
- [(def .public <name>
- (-> Int Int)
- (+ <diff>))]
-
- [++ +1]
- [-- -1]
- )])
-
- (documentation /.not
- "Bit negation."
- [(not #1)
- "=>"
- #0]
- [(not #0)
- "=>"
- #1])
-
- (documentation /.type
- "Takes a type expression and returns its representation as data-structure."
- [(type_literal (All (_ a)
- (Maybe (List a))))])
-
- (documentation /.is
- "The type-annotation macro."
- [(is (List Int)
- (list +1 +2 +3))])
-
- (documentation /.as
- "The type-coercion macro."
- [(as Dinosaur
- (list +1 +2 +3))])
-
- (documentation /.Rec
- "Parameter-less recursive types."
- ["A name has to be given to the whole type, to use it within its body."
- (Rec Int_List
- (Or Any
- [Int Int_List]))]
- ["Can also be used with type and labelled-type definitions."
- (type Type
- (Rec @
- (Variant
- {#Primitive Text (List @)}
- {#Sum @ @}
- {#Product @ @}
- {#Function @ @}
- {#Parameter Nat}
- {#Var Nat}
- {#Ex Nat}
- {#UnivQ (List @) @}
- {#ExQ (List @) @}
- {#Apply @ @}
- {#Named Symbol @})))])
-
- (documentation /.exec
- "Sequential execution of expressions (great for side-effects)."
- [(exec
- (log! "#1")
- (log! "#2")
- (log! "#3")
- "YOLO")])
-
- (documentation /.case
- (format "The pattern-matching macro."
- \n "Allows the usage of macros within the patterns to provide custom syntax.")
- [(case (is (List Int)
- (list +1 +2 +3))
- {#Item x {#Item y {#Item z {#End}}}}
- {#Some (all * x y z)}
-
- _
- {#None})])
-
- (documentation /.pattern
- (format "Macro-expanding patterns."
- \n "It's a special macro meant to be used with 'case'.")
- [(case (is (List Int)
- (list +1 +2 +3))
- (pattern (list x y z))
- {#Some (all * x y z)}
-
- _
- {#None})])
-
- ... (documentation /.^or
- ... (format "Or-patterns."
- ... \n "It's a special macro meant to be used with 'case'.")
- ... [(type Weekday
- ... (Variant
- ... {#Monday}
- ... {#Tuesday}
- ... {#Wednesday}
- ... {#Thursday}
- ... {#Friday}
- ... {#Saturday}
- ... {#Sunday}))
-
- ... (def (weekend? day)
- ... (-> Weekday Bit)
- ... (case day
- ... (^or {#Saturday} {#Sunday})
- ... #1
-
- ... _
- ... #0))])
-
- (documentation /.let
- (format "Creates local bindings."
- \n "Can (optionally) use pattern-matching macros when binding.")
- [(let [x (foo bar)
- y (baz quux)]
- (op x y))])
-
- (documentation /.function
- "Syntax for creating functions."
- [(is (All (_ a b)
- (-> a b a))
- (function (_ x y)
- x))]
- ["Allows for giving the function itself a name, for the sake of recursion."
- (is (-> Nat Nat)
- (function (factorial n)
- (case n
- 0 1
- _ (* n (factorial (-- n))))))])
-
- (documentation /.def
- "Defines global constants/functions."
- [(def branching_exponent
- Int
- +5)]
- ["The type is optional."
- (def branching_exponent
- +5)]
- [(def (pair_list pair)
- (-> [Code Code] (List Code))
- (let [[left right] pair]
- (list left right)))]
- ["Can pattern-match on the inputs to functions."
- (def (pair_list [left right])
- (-> [Code Code] (List Code))
- (list left right))])
-
- (documentation /.macro
- "Macro-definition macro."
- [(def .public symbol
- (macro (_ tokens)
- (case tokens
- (^with_template [<tag>]
- [(pattern (list [_ {<tag> [module name]}]))
- (in (list (` [(~ (text$ module)) (~ (text$ name))])))])
- ([#Symbol])
-
- _
- (failure "Wrong syntax for symbol"))))])
-
- (documentation /.and
- "Short-circuiting 'and'."
- [(and #1 #0)
- "=>"
- #0]
- [(and #1 #1)
- "=>"
- #1])
-
- (documentation /.or
- "Short-circuiting 'or'."
- [(or #1 #0)
- "=>"
- #1]
- [(or #0 #0)
- "=>"
- #0])
-
- (documentation /.panic!
- "Causes an error, with the given error message."
- [(panic! "OH NO!")])
-
- (documentation /.implementation
- "Express a value that implements an interface."
- [(is (Order Int)
- (implementation
- (def equivalence
- equivalence)
- (def (< reference subject)
- (< reference subject))
- ))])
-
- (documentation /.Variant
- (format "Syntax for defining labelled/tagged sum/union types."
- \n "WARNING: Only use it within the type macro.")
- [(type Referrals
- (Variant
- {#All}
- {#Only (List Text)}
- {#Exclude (List Text)}
- {#Ignore}
- {#Nothing}))])
-
- (documentation /.Record
- (format "Syntax for defining labelled/slotted product/tuple types."
- \n "WARNING: Only use it within the type macro.")
- [(type Refer
- (Record
- [#refer_defs Referrals
- #refer_open (List Openings)]))])
-
- (documentation /.type
- "The type-definition macro."
- [(type (List a)
- {#End}
- {#Item a (List a)})])
-
- (documentation /.Interface
- "Interface definition."
- [(type .public (Order a)
- (Interface
- (is (Equivalence a)
- equivalence)
- (is (-> a a Bit)
- <)))])
-
- (.with_template [<name>]
- [(documentation <name>
- "Safe type-casting for I64 values.")]
-
- [/.i64]
- [/.nat]
- [/.int]
- [/.rev]
- )
-
- (documentation /.module_separator
- (format "Character used to separate the parts of module names."
- \n "Value: " (%.text /.module_separator)))
-
- (documentation /.open
- (format "Same as the 'open' macro, but meant to be used as a pattern-matching macro for generating local bindings."
- \n "Takes an 'alias' text for the generated local bindings.")
- [(def .public (range enum from to)
- (All (_ a) (-> (Enum a) a a (List a)))
- (let [(open "[0]") enum]
- (loop (again [end to
- output {.#End}])
- (cond (< end from)
- (again (pred end) {.#Item end output})
-
- (< from end)
- (again (succ end) {.#Item end output})
-
- ... (= end from)
- {.#Item end output}))))])
-
- (documentation /.cond
- "Conditional branching with multiple test conditions."
- [(cond (even? num) "WHEN even"
- (odd? num) "WHEN odd"
- "ELSE")])
-
- (documentation /.the
- "Accesses the value of a record at a given tag."
- [(the #field my_record)]
- ["Can also work with multiple levels of nesting."
- (the [#foo #bar #baz] my_record)]
- ["And, if only the slot/path is given, generates an accessor function."
- (let [getter (the [#foo #bar #baz])]
- (getter my_record))])
-
- (documentation /.use
- "Opens a implementation and generates a definition for each of its members (including nested members)."
- [(use "i:[0]" order)
- "=>"
- (def i:= (at order =))
- (def i:< (at order <))])
-
- (documentation /.|>>
- "Similar to the piping macro, but rather than taking an initial object to work on, creates a function for taking it."
- [(|>> (list#each int#encoded)
- (interposed " ")
- (mix text#composite ""))
- "=>"
- (function (_ <it>)
- (mix text#composite ""
- (interposed " "
- (list#each int#encoded <it>))))])
-
- (documentation /.<<|
- "Similar to the reverse piping macro, but rather than taking an initial object to work on, creates a function for taking it."
- [(<<| (mix text#composite "")
- (interposed " ")
- (list#each int#encoded))
- "=>"
- (function (_ <it>)
- (mix text#composite ""
- (interposed " "
- (list#each int#encoded
- <it>))))])
-
- (documentation /.require
- "Module-definition macro."
- [(.require
- [lux (.except)
- [control
- ["M" monad (.except)]]
- [data
- maybe
- ["[0]" name (.use "[1]#[0]" codec)]]
- [macro
- code]]
- [//
- [type (.use "[0]" equivalence)]])])
-
- (documentation /.#
- "Allows accessing the value of a implementation's member."
- [(at codec encoded)]
- ["Also allows using that value as a function."
- (at codec encoded +123)])
-
- (documentation /.has
- "Sets the value of a record at a given tag."
- [(has #name "Lux" lang)]
- ["Can also work with multiple levels of nesting."
- (has [#foo #bar #baz] value my_record)]
- ["And, if only the slot/path and (optionally) the value are given, generates a mutator function."
- (let [setter (has [#foo #bar #baz] value)]
- (setter my_record))
- (let [setter (has [#foo #bar #baz])]
- (setter value my_record))])
-
- (documentation /.revised
- "Modifies the value of a record at a given tag, based on some function."
- [(revised #age ++ person)]
- ["Can also work with multiple levels of nesting."
- (revised [#foo #bar #baz] func my_record)]
- ["And, if only the slot/path and (optionally) the value are given, generates a mutator function."
- (let [updater (revised [#foo #bar #baz] func)]
- (updater my_record))
- (let [updater (revised [#foo #bar #baz])]
- (updater func my_record))])
-
- ... (documentation /.^template
- ... "It's similar to template, but meant to be used during pattern-matching."
- ... [(def (reduced env type)
- ... (-> (List Type) Type Type)
- ... (case type
- ... {.#Primitive name params}
- ... {.#Primitive name (list#each (reduced env) params)}
-
- ... (^with_template [<tag>]
- ... [{<tag> left right}
- ... {<tag> (reduced env left) (reduced env right)}])
- ... ([.#Sum] [.#Product])
-
- ... (^with_template [<tag>]
- ... [{<tag> left right}
- ... {<tag> (reduced env left) (reduced env right)}])
- ... ([.#Function] [.#Apply])
-
- ... (^with_template [<tag>]
- ... [{<tag> old_env def}
- ... (case old_env
- ... {.#End}
- ... {<tag> env def}
-
- ... _
- ... type)])
- ... ([.#UnivQ] [.#ExQ])
-
- ... {.#Parameter idx}
- ... (else type (list.item idx env))
-
- ... _
- ... type
- ... ))])
-
- (.with_template [<name> <doc>]
- [(documentation <name>
- <doc>)]
-
- [/.++ "Increment function."]
- [/.-- "Decrement function."]
- )
-
- (documentation /.loop
- (format "Allows arbitrary looping, using the 'again' form to re-start the loop."
- \n "Can be used in monadic code to create monadic loops.")
- [(loop (again [count +0
- x init])
- (if (< +10 count)
- (again (++ count) (f x))
- x))]
- ["Loops can also be given custom names."
- (loop (my_loop [count +0
- x init])
- (if (< +10 count)
- (my_loop (++ count) (f x))
- x))])
-
- (documentation /.with_expansions
- (format "Controlled macro-expansion."
- \n "Bind an arbitraty number of Code nodes resulting from macro-expansion to local bindings."
- \n "Wherever a binding appears, the bound Code nodes will be spliced in there.")
- [(def test
- Test
- (with_expansions
- [<tests> (with_template [<function> <parameter> <expected>]
- [(cover [<function>]
- (compare <text>
- (at codec encoded <function> <parameter>)))]
-
- [bit #1 "#1"]
- [int +123 "+123"]
- [frac +123.0 "+123.0"]
- [text "123" "'123'"]
- [symbol ["yolo" "lol"] "yolo.lol"]
- [form (list (bit #1)) "(#1)"]
- [tuple (list (bit #1)) "[#1]"]
- )]
- (all and
- <tests>
- )))])
-
- (documentation /.static
- (format "Resolves the names of definitions to their values at compile-time, assuming their values are either:"
- \n "* Bit"
- \n "* Nat"
- \n "* Int"
- \n "* Rev"
- \n "* Frac"
- \n "* Text")
- [(def my_nat 123)
- (def my_text "456")
- (and (case [my_nat my_text]
- (pattern (static [..my_nat ..my_text]))
- true
+ ($.documentation /.Location
+ "Locations are for specifying the location of Code nodes in Lux files during compilation.")
+
+ ($.documentation (/.Ann meta_data datum)
+ "The type of things that can be annotated with meta-data of arbitrary types.")
+
+ ($.documentation /.Code
+ "The type of Code nodes for Lux syntax.")
+
+ ($.documentation /.private
+ "The export policy for private/local definitions.")
+
+ ($.documentation /.local
+ "The export policy for private/local definitions.")
+
+ ($.documentation /.public
+ "The export policy for public/global definitions.")
+
+ ($.documentation /.global
+ "The export policy for public/global definitions.")
+
+ ($.documentation /.Definition
+ "Represents all the data associated with a definition: its type, its annotations, and its value.")
+
+ ($.documentation /.Global
+ "Represents all the data associated with a global constant.")
+
+ ($.documentation (/.Either left right)
+ "A choice between two values of different types.")
+
+ ($.documentation /.Module
+ "All the information contained within a Lux module.")
+
+ ($.documentation /.Mode
+ "A sign that shows the conditions under which the compiler is running.")
+
+ ($.documentation /.Info
+ "Information about the current version and type of compiler that is running.")
+
+ ($.documentation /.Lux
+ (format "Represents the state of the Lux compiler during a run."
+ \n "It is provided to macros during their invocation, so they can access compiler data."
+ \n "Caveat emptor: Avoid fiddling with it, unless you know what you're doing."))
+
+ ($.documentation (/.Meta it)
+ (format "Computations that can have access to the state of the compiler."
+ \n "These computations may fail, or modify the state of the compiler."))
+
+ ($.documentation /.Macro
+ "Functions that run at compile-time and allow you to transform and extend the language in powerful ways.")
+
+ ($.documentation /.comment
+ (format "Throws away any code given to it."
+ \n "Great for commenting-out code, while retaining syntax high-lighting and formatting in your text editor.")
+ [(comment
+ (def (this will not)
+ (Be Defined)
+ (because it will be (commented out))))])
+
+ ($.documentation /.All
+ "Universal quantification."
+ [(All (_ a)
+ (-> a a))]
+ ["A name can be provided, to specify a recursive type."
+ (All (List a)
+ (Or Any
+ [a (List a)]))])
+
+ ($.documentation /.Ex
+ "Existential quantification."
+ [(Ex (_ a)
+ [(Codec Text a) a])]
+ ["A name can be provided, to specify a recursive type."
+ (Ex (Self a)
+ [(Codec Text a)
+ a
+ (List (Self a))])])
+
+ ($.documentation /.->
+ "Function types."
+ ["This is the type of a function that takes 2 Ints and returns an Int."
+ (-> Int Int Int)])
+
+ ($.documentation /.list
+ "List literals."
+ [(is (List Nat)
+ (list 0 1 2 3))])
+
+ ($.documentation /.Union
+ "Union types."
+ [(Union Bit Nat Text)]
+ [(= Nothing
+ (Union))])
+
+ ($.documentation /.Tuple
+ "Tuple types."
+ [(Tuple Bit Nat Text)]
+ [(= Any
+ (Tuple))])
+
+ ($.documentation /.Or
+ "An alias for the Union type constructor."
+ [(= (Union Bit Nat Text)
+ (Or Bit Nat Text))]
+ [(= (Union)
+ (Or))])
+
+ ($.documentation /.And
+ "An alias for the Tuple type constructor."
+ [(= (Tuple Bit Nat Text)
+ (And Bit Nat Text))]
+ [(= (Tuple)
+ (And))])
+
+ ($.documentation /.left
+ "Left-association for the application of binary functions over variadic arguments."
+ [(left text#composite "Hello, " name ". How are you?")
+ "=>"
+ (text#composite (text#composite "Hello, " name) ". How are you?")])
+
+ ($.documentation /.all
+ "Right-association for the application of binary functions over variadic arguments."
+ [(all text#composite "Hello, " name ". How are you?")
+ "=>"
+ (text#composite "Hello, " (text#composite name ". How are you?"))])
+
+ ($.documentation /.if
+ "Picks which expression to evaluate based on a bit test value."
+ [(if #1
+ "Oh, yeah!"
+ "Aw hell naw!")
+ "=>"
+ "Oh, yeah!"]
+ [(if #0
+ "Oh, yeah!"
+ "Aw hell naw!")
+ "=>"
+ "Aw hell naw!"])
+
+ ($.documentation /.Primitive
+ "Macro to treat define new primitive types."
+ [(Primitive "java.lang.Object")]
+ [(Primitive "java.util.List" [(Primitive "java.lang.Long")])])
+
+ ($.documentation /.`
+ (format "Hygienic quasi-quotation as a macro."
+ \n "Unquote (~) and unquote-splice (~+) must also be used as forms."
+ \n "All unprefixed macros will receive their parent module's prefix if imported; otherwise will receive the prefix of the module on which the quasi-quote is being used.")
+ [(` (def (~ name)
+ (function ((~' _) (~+ args))
+ (~ body))))])
+
+ ($.documentation /.`'
+ (format "Unhygienic quasi-quotation as a macro."
+ \n "Unquote (~) and unquote-splice (~+) must also be used as forms.")
+ [(`' (def (~ name)
+ (function (_ (~+ args))
+ (~ body))))])
+
+ ($.documentation /.'
+ "Quotation as a macro."
+ [(' YOLO)])
+
+ ($.documentation /.|>
+ "Piping macro."
+ [(|> elems
+ (list#each int#encoded)
+ (interposed " ")
+ (mix text#composite ""))
+ "=>"
+ (mix text#composite ""
+ (interposed " "
+ (list#each int#encoded
+ elems)))])
+
+ ($.documentation /.<|
+ "Reverse piping macro."
+ [(<| (mix text#composite "")
+ (interposed " ")
+ (list#each int#encoded)
+ elems)
+ "=>"
+ (mix text#composite ""
+ (interposed " "
+ (list#each int#encoded
+ elems)))])
+
+ ($.documentation /.template
+ ""
+ ["By specifying a pattern (with holes), and the input data to fill those holes, repeats the pattern as many times as necessary."
+ (with_template [<name> <diff>]
+ [(def .public <name>
+ (-> Int Int)
+ (+ <diff>))]
+
+ [++ +1]
+ [-- -1]
+ )])
+
+ ($.documentation /.not
+ "Bit negation."
+ [(not #1)
+ "=>"
+ #0]
+ [(not #0)
+ "=>"
+ #1])
+
+ ($.documentation /.type
+ "Takes a type expression and returns its representation as data-structure."
+ [(type_literal (All (_ a)
+ (Maybe (List a))))])
+
+ ($.documentation /.is
+ "The type-annotation macro."
+ [(is (List Int)
+ (list +1 +2 +3))])
+
+ ($.documentation /.as
+ "The type-coercion macro."
+ [(as Dinosaur
+ (list +1 +2 +3))])
+
+ ($.documentation /.Rec
+ "Parameter-less recursive types."
+ ["A name has to be given to the whole type, to use it within its body."
+ (Rec Int_List
+ (Or Any
+ [Int Int_List]))]
+ ["Can also be used with type and labelled-type definitions."
+ (type Type
+ (Rec @
+ (Variant
+ {#Primitive Text (List @)}
+ {#Sum @ @}
+ {#Product @ @}
+ {#Function @ @}
+ {#Parameter Nat}
+ {#Var Nat}
+ {#Ex Nat}
+ {#UnivQ (List @) @}
+ {#ExQ (List @) @}
+ {#Apply @ @}
+ {#Named Symbol @})))])
+
+ ($.documentation /.exec
+ "Sequential execution of expressions (great for side-effects)."
+ [(exec
+ (log! "#1")
+ (log! "#2")
+ (log! "#3")
+ "YOLO")])
+
+ ($.documentation /.case
+ (format "The pattern-matching macro."
+ \n "Allows the usage of macros within the patterns to provide custom syntax.")
+ [(case (is (List Int)
+ (list +1 +2 +3))
+ {#Item x {#Item y {#Item z {#End}}}}
+ {#Some (all * x y z)}
_
- false)
- (case [my_nat my_text]
- (pattern [(static ..my_nat) (static ..my_text)])
- true
+ {#None})])
+
+ ($.documentation /.pattern
+ (format "Macro-expanding patterns."
+ \n "It's a special macro meant to be used with 'case'.")
+ [(case (is (List Int)
+ (list +1 +2 +3))
+ (pattern (list x y z))
+ {#Some (all * x y z)}
_
- false))])
-
- ... (documentation /.^multi
- ... (format "Multi-level pattern matching."
- ... \n "Useful in situations where the result of a branch depends on further refinements on the values being matched.")
- ... [(case (split (size static) uri)
- ... (^multi {#Some [chunk uri']}
- ... [(text#= static chunk) #1])
- ... (match_uri endpoint? parts' uri')
-
- ... _
- ... {#Left (format "Static part " (%t static) " does not match URI: " uri)})]
- ... ["Short-cuts can be taken when using bit tests."
- ... "The example above can be rewritten as..."
- ... (case (split (size static) uri)
- ... (^multi {#Some [chunk uri']}
- ... (text#= static chunk))
- ... (match_uri endpoint? parts' uri')
-
- ... _
- ... {#Left (format "Static part " (%t static) " does not match URI: " uri)})])
-
- (documentation /.symbol
- "Gives back a 2 tuple with the module and name parts, both as Text."
- [(symbol ..#doc)
- "=>"
- ["documentation/lux" "#doc"]])
-
- (documentation /.parameter
- (format "WARNING: Please stay away from this macro; it's very likely to be removed in a future version of Lux."
- "Allows you to refer to the type-variables in a polymorphic function's type, by their index.")
- ["In the example below, 0 corresponds to the 'a' variable."
- (def .public (of_list list)
- (All (_ a) (-> (List a) (Sequence a)))
- (list#mix add
- (is (Sequence (parameter 0))
- empty)
- list))])
-
- (documentation /.same?
- "Tests whether the 2 values are identical (not just 'equal')."
- ["This one should succeed:"
- (let [value +5]
- (same? value
- value))]
- ["This one should fail:"
- (same? +5
- (+ +2 +3))])
-
- ... (documentation /.^let
- ... "Allows you to simultaneously bind and de-structure a value."
- ... [(def (hash (^let set [member_hash _]))
- ... (list#mix (function (_ elem acc)
- ... (+ acc
- ... (at member_hash hash elem)))
- ... 0
- ... (set.list set)))])
-
- ... (documentation /.^|>
- ... "Pipes the value being pattern-matched against prior to binding it to a variable."
- ... [(case input
- ... (^|> value [++ (% 10) (max 1)])
- ... (foo value))])
-
- (documentation /.as_expected
- "Coerces the given expression to the type of whatever is expected."
- [(is Dinosaur
- (as_expected (is (List Nat)
- (list 1 2 3))))])
-
- (documentation /.undefined
- (format "Meant to be used as a stand-in for functions with undefined implementations."
- \n "Undefined expressions will type-check against everything, so they make good dummy implementations."
- \n "However, if an undefined expression is ever evaluated, it will raise a runtime error.")
- [(def (square x)
- (-> Int Int)
- (undefined))])
-
- (documentation /.type_of
- "Generates the type corresponding to a given expression."
- [(let [my_num +123]
- (type_of my_num))
- "=="
- Int]
- [(type_of +123)
- "=="
- Int])
-
- (documentation /.template
- (format "Define macros in the style of with_template."
- \n "For simple macros that do not need any fancy features.")
- [(def square
- (template (square x)
- (* x x)))])
-
- (documentation /.these
- (format "Given a (potentially empty) list of codes, just returns them immediately, without any work done."
- \n "This may seen useless, but it has its utility when dealing with controlled-macro-expansion macros.")
- [(with_expansions [<operands> (these 1
- 2
- 3
- 4)]
- (all + <operands>))])
-
- (documentation /.char
- "If given a 1-character text literal, yields the char-code of the sole character."
- [(is Nat
- (char "A"))
- "=>"
- 65])
-
- (documentation /.for
- (format "Selects the appropriate code for a given target-platform when compiling Lux to it."
- \n "Look-up the available targets in library/lux/target.")
- [(def js
- "JavaScript")
-
- (for "JVM" (do jvm stuff)
- js (do js stuff)
- (do default stuff))])
-
- (documentation /.``
- (format "Delimits a controlled (spliced) macro-expansion."
- \n "Uses a (~~) special form to specify where to expand.")
- [(`` (some expression
- (~~ (some macro which may yield 0 or more results))))])
-
- ... (documentation /.^code
- ... "Generates pattern-matching code for Code values in a way that looks like code-templating."
- ... [(is (Maybe Nat)
- ... (case (` (#0 123 +456.789))
- ... (^code (#0 (~ [_ {.#Nat number}]) +456.789))
- ... {.#Some number}
-
- ... _
- ... {.#None}))])
-
- (documentation /.false
- "The boolean FALSE value.")
-
- (documentation /.true
- "The boolean TRUE value.")
-
- (documentation /.try
- ""
- [(is Foo
- (case (is (Either Text Bar)
- (try (is Bar
- (risky computation which may panic))))
- {.#Right success}
- (is Foo
- (do something after success))
-
- {.#Left error}
- (is Foo
- (recover from error))))])
-
- ($.default (/.Code' w))
- ($.default /.Alias)
- ($.default (/.Bindings key value))
- ($.default /.Ref)
- ($.default /.Scope)
- ($.default /.Source)
- ($.default /.Module_State)
- ($.default /.Type_Context)
- ($.default /.Macro')
- ($.default /.Label)
- ($.default /.macro)]
- [/abstract.documentation
- /control.documentation
- /data.documentation
- /debug.documentation
- /documentation.documentation
- /extension.documentation
- /ffi.documentation
- /locale.documentation
- /macro.documentation
- /math.documentation
- /meta.documentation
- /program.documentation
- /static.documentation
- /target.documentation
- /test.documentation
- /time.documentation
- /tool.documentation
- /type.documentation
- /world.documentation]))
+ {#None})])
+
+ ... ($.documentation /.^or
+ ... (format "Or-patterns."
+ ... \n "It's a special macro meant to be used with 'case'.")
+ ... [(type Weekday
+ ... (Variant
+ ... {#Monday}
+ ... {#Tuesday}
+ ... {#Wednesday}
+ ... {#Thursday}
+ ... {#Friday}
+ ... {#Saturday}
+ ... {#Sunday}))
+
+ ... (def (weekend? day)
+ ... (-> Weekday Bit)
+ ... (case day
+ ... (^or {#Saturday} {#Sunday})
+ ... #1
+
+ ... _
+ ... #0))])
+
+ ($.documentation /.let
+ (format "Creates local bindings."
+ \n "Can (optionally) use pattern-matching macros when binding.")
+ [(let [x (foo bar)
+ y (baz quux)]
+ (op x y))])
+
+ ($.documentation /.function
+ "Syntax for creating functions."
+ [(is (All (_ a b)
+ (-> a b a))
+ (function (_ x y)
+ x))]
+ ["Allows for giving the function itself a name, for the sake of recursion."
+ (is (-> Nat Nat)
+ (function (factorial n)
+ (case n
+ 0 1
+ _ (* n (factorial (-- n))))))])
+
+ ($.documentation /.def
+ "Defines global constants/functions."
+ [(def branching_exponent
+ Int
+ +5)]
+ ["The type is optional."
+ (def branching_exponent
+ +5)]
+ [(def (pair_list pair)
+ (-> [Code Code] (List Code))
+ (let [[left right] pair]
+ (list left right)))]
+ ["Can pattern-match on the inputs to functions."
+ (def (pair_list [left right])
+ (-> [Code Code] (List Code))
+ (list left right))])
+
+ ($.documentation /.macro
+ "Macro-definition macro."
+ [(def .public symbol
+ (macro (_ tokens)
+ (case tokens
+ (^with_template [<tag>]
+ [(pattern (list [_ {<tag> [module name]}]))
+ (in (list (` [(~ (text$ module)) (~ (text$ name))])))])
+ ([#Symbol])
+
+ _
+ (failure "Wrong syntax for symbol"))))])
+
+ ($.documentation /.and
+ "Short-circuiting 'and'."
+ [(and #1 #0)
+ "=>"
+ #0]
+ [(and #1 #1)
+ "=>"
+ #1])
+
+ ($.documentation /.or
+ "Short-circuiting 'or'."
+ [(or #1 #0)
+ "=>"
+ #1]
+ [(or #0 #0)
+ "=>"
+ #0])
+
+ ($.documentation /.panic!
+ "Causes an error, with the given error message."
+ [(panic! "OH NO!")])
+
+ ($.documentation /.implementation
+ "Express a value that implements an interface."
+ [(is (Order Int)
+ (implementation
+ (def equivalence
+ equivalence)
+ (def (< reference subject)
+ (< reference subject))
+ ))])
+
+ ($.documentation /.Variant
+ (format "Syntax for defining labelled/tagged sum/union types."
+ \n "WARNING: Only use it within the type macro.")
+ [(type Referrals
+ (Variant
+ {#All}
+ {#Only (List Text)}
+ {#Exclude (List Text)}
+ {#Ignore}
+ {#Nothing}))])
+
+ ($.documentation /.Record
+ (format "Syntax for defining labelled/slotted product/tuple types."
+ \n "WARNING: Only use it within the type macro.")
+ [(type Refer
+ (Record
+ [#refer_defs Referrals
+ #refer_open (List Openings)]))])
+
+ ($.documentation /.type
+ "The type-definition macro."
+ [(type (List a)
+ {#End}
+ {#Item a (List a)})])
+
+ ($.documentation /.Interface
+ "Interface definition."
+ [(type .public (Order a)
+ (Interface
+ (is (Equivalence a)
+ equivalence)
+ (is (-> a a Bit)
+ <)))])
+
+ (.~~ (.with_template [<name>]
+ [($.documentation <name>
+ "Safe type-casting for I64 values.")]
+
+ [/.i64]
+ [/.nat]
+ [/.int]
+ [/.rev]
+ ))
+
+ ($.documentation /.module_separator
+ (format "Character used to separate the parts of module names."
+ \n "Value: " (%.text /.module_separator)))
+
+ ($.documentation /.open
+ (format "Same as the 'open' macro, but meant to be used as a pattern-matching macro for generating local bindings."
+ \n "Takes an 'alias' text for the generated local bindings.")
+ [(def .public (range enum from to)
+ (All (_ a) (-> (Enum a) a a (List a)))
+ (let [(open "[0]") enum]
+ (loop (again [end to
+ output {.#End}])
+ (cond (< end from)
+ (again (pred end) {.#Item end output})
+
+ (< from end)
+ (again (succ end) {.#Item end output})
+
+ ... (= end from)
+ {.#Item end output}))))])
+
+ ($.documentation /.cond
+ "Conditional branching with multiple test conditions."
+ [(cond (even? num) "WHEN even"
+ (odd? num) "WHEN odd"
+ "ELSE")])
+
+ ($.documentation /.the
+ "Accesses the value of a record at a given tag."
+ [(the #field my_record)]
+ ["Can also work with multiple levels of nesting."
+ (the [#foo #bar #baz] my_record)]
+ ["And, if only the slot/path is given, generates an accessor function."
+ (let [getter (the [#foo #bar #baz])]
+ (getter my_record))])
+
+ ($.documentation /.use
+ "Opens a implementation and generates a definition for each of its members (including nested members)."
+ [(use "i:[0]" order)
+ "=>"
+ (def i:= (at order =))
+ (def i:< (at order <))])
+
+ ($.documentation /.|>>
+ "Similar to the piping macro, but rather than taking an initial object to work on, creates a function for taking it."
+ [(|>> (list#each int#encoded)
+ (interposed " ")
+ (mix text#composite ""))
+ "=>"
+ (function (_ <it>)
+ (mix text#composite ""
+ (interposed " "
+ (list#each int#encoded <it>))))])
+
+ ($.documentation /.<<|
+ "Similar to the reverse piping macro, but rather than taking an initial object to work on, creates a function for taking it."
+ [(<<| (mix text#composite "")
+ (interposed " ")
+ (list#each int#encoded))
+ "=>"
+ (function (_ <it>)
+ (mix text#composite ""
+ (interposed " "
+ (list#each int#encoded
+ <it>))))])
+
+ ($.documentation /.require
+ "Module-definition macro."
+ [(.require
+ [lux (.except)
+ [control
+ ["M" monad (.except)]]
+ [data
+ maybe
+ ["[0]" name (.use "[1]#[0]" codec)]]
+ [macro
+ code]]
+ [//
+ [type (.use "[0]" equivalence)]])])
+
+ ($.documentation /.at
+ "Allows accessing the value of a implementation's member."
+ [(at codec encoded)]
+ ["Also allows using that value as a function."
+ (at codec encoded +123)])
+
+ ($.documentation /.has
+ "Sets the value of a record at a given tag."
+ [(has #name "Lux" lang)]
+ ["Can also work with multiple levels of nesting."
+ (has [#foo #bar #baz] value my_record)]
+ ["And, if only the slot/path and (optionally) the value are given, generates a mutator function."
+ (let [setter (has [#foo #bar #baz] value)]
+ (setter my_record))
+ (let [setter (has [#foo #bar #baz])]
+ (setter value my_record))])
+
+ ($.documentation /.revised
+ "Modifies the value of a record at a given tag, based on some function."
+ [(revised #age ++ person)]
+ ["Can also work with multiple levels of nesting."
+ (revised [#foo #bar #baz] func my_record)]
+ ["And, if only the slot/path and (optionally) the value are given, generates a mutator function."
+ (let [updater (revised [#foo #bar #baz] func)]
+ (updater my_record))
+ (let [updater (revised [#foo #bar #baz])]
+ (updater func my_record))])
+
+ ... ($.documentation /.^template
+ ... "It's similar to template, but meant to be used during pattern-matching."
+ ... [(def (reduced env type)
+ ... (-> (List Type) Type Type)
+ ... (case type
+ ... {.#Primitive name params}
+ ... {.#Primitive name (list#each (reduced env) params)}
+
+ ... (^with_template [<tag>]
+ ... [{<tag> left right}
+ ... {<tag> (reduced env left) (reduced env right)}])
+ ... ([.#Sum] [.#Product])
+
+ ... (^with_template [<tag>]
+ ... [{<tag> left right}
+ ... {<tag> (reduced env left) (reduced env right)}])
+ ... ([.#Function] [.#Apply])
+
+ ... (^with_template [<tag>]
+ ... [{<tag> old_env def}
+ ... (case old_env
+ ... {.#End}
+ ... {<tag> env def}
+
+ ... _
+ ... type)])
+ ... ([.#UnivQ] [.#ExQ])
+
+ ... {.#Parameter idx}
+ ... (else type (list.item idx env))
+
+ ... _
+ ... type
+ ... ))])
+
+ (.~~ (.with_template [<name> <doc>]
+ [($.documentation <name>
+ <doc>)]
+
+ [/.++ "Increment function."]
+ [/.-- "Decrement function."]
+ ))
+
+ ($.documentation /.loop
+ (format "Allows arbitrary looping, using the 'again' form to re-start the loop."
+ \n "Can be used in monadic code to create monadic loops.")
+ [(loop (again [count +0
+ x init])
+ (if (< +10 count)
+ (again (++ count) (f x))
+ x))]
+ ["Loops can also be given custom names."
+ (loop (my_loop [count +0
+ x init])
+ (if (< +10 count)
+ (my_loop (++ count) (f x))
+ x))])
+
+ ($.documentation /.with_expansions
+ (format "Controlled macro-expansion."
+ \n "Bind an arbitraty number of Code nodes resulting from macro-expansion to local bindings."
+ \n "Wherever a binding appears, the bound Code nodes will be spliced in there.")
+ [(def test
+ Test
+ (with_expansions
+ [<tests> (with_template [<function> <parameter> <expected>]
+ [(cover [<function>]
+ (compare <text>
+ (at codec encoded <function> <parameter>)))]
+
+ [bit #1 "#1"]
+ [int +123 "+123"]
+ [frac +123.0 "+123.0"]
+ [text "123" "'123'"]
+ [symbol ["yolo" "lol"] "yolo.lol"]
+ [form (list (bit #1)) "(#1)"]
+ [tuple (list (bit #1)) "[#1]"]
+ )]
+ (all and
+ <tests>
+ )))])
+
+ ($.documentation /.static
+ (format "Resolves the names of definitions to their values at compile-time, assuming their values are either:"
+ \n "* Bit"
+ \n "* Nat"
+ \n "* Int"
+ \n "* Rev"
+ \n "* Frac"
+ \n "* Text")
+ [(def my_nat 123)
+ (def my_text "456")
+ (and (case [my_nat my_text]
+ (pattern (static [..my_nat ..my_text]))
+ true
+
+ _
+ false)
+ (case [my_nat my_text]
+ (pattern [(static ..my_nat) (static ..my_text)])
+ true
+
+ _
+ false))])
+
+ ... ($.documentation /.^multi
+ ... (format "Multi-level pattern matching."
+ ... \n "Useful in situations where the result of a branch depends on further refinements on the values being matched.")
+ ... [(case (split (size static) uri)
+ ... (^multi {#Some [chunk uri']}
+ ... [(text#= static chunk) #1])
+ ... (match_uri endpoint? parts' uri')
+
+ ... _
+ ... {#Left (format "Static part " (%t static) " does not match URI: " uri)})]
+ ... ["Short-cuts can be taken when using bit tests."
+ ... "The example above can be rewritten as..."
+ ... (case (split (size static) uri)
+ ... (^multi {#Some [chunk uri']}
+ ... (text#= static chunk))
+ ... (match_uri endpoint? parts' uri')
+
+ ... _
+ ... {#Left (format "Static part " (%t static) " does not match URI: " uri)})])
+
+ ($.documentation /.symbol
+ "Gives back a 2 tuple with the module and name parts, both as Text."
+ [(symbol ..#doc)
+ "=>"
+ ["documentation/lux" "#doc"]])
+
+ ($.documentation /.parameter
+ (format "WARNING: Please stay away from this macro; it's very likely to be removed in a future version of Lux."
+ "Allows you to refer to the type-variables in a polymorphic function's type, by their index.")
+ ["In the example below, 0 corresponds to the 'a' variable."
+ (def .public (of_list list)
+ (All (_ a) (-> (List a) (Sequence a)))
+ (list#mix add
+ (is (Sequence (parameter 0))
+ empty)
+ list))])
+
+ ($.documentation /.same?
+ "Tests whether the 2 values are identical (not just 'equal')."
+ ["This one should succeed:"
+ (let [value +5]
+ (same? value
+ value))]
+ ["This one should fail:"
+ (same? +5
+ (+ +2 +3))])
+
+ ... ($.documentation /.^let
+ ... "Allows you to simultaneously bind and de-structure a value."
+ ... [(def (hash (^let set [member_hash _]))
+ ... (list#mix (function (_ elem acc)
+ ... (+ acc
+ ... (at member_hash hash elem)))
+ ... 0
+ ... (set.list set)))])
+
+ ... ($.documentation /.^|>
+ ... "Pipes the value being pattern-matched against prior to binding it to a variable."
+ ... [(case input
+ ... (^|> value [++ (% 10) (max 1)])
+ ... (foo value))])
+
+ ($.documentation /.as_expected
+ "Coerces the given expression to the type of whatever is expected."
+ [(is Dinosaur
+ (as_expected (is (List Nat)
+ (list 1 2 3))))])
+
+ ($.documentation /.undefined
+ (format "Meant to be used as a stand-in for functions with undefined implementations."
+ \n "Undefined expressions will type-check against everything, so they make good dummy implementations."
+ \n "However, if an undefined expression is ever evaluated, it will raise a runtime error.")
+ [(def (square x)
+ (-> Int Int)
+ (undefined))])
+
+ ($.documentation /.type_of
+ "Generates the type corresponding to a given expression."
+ [(let [my_num +123]
+ (type_of my_num))
+ "=="
+ Int]
+ [(type_of +123)
+ "=="
+ Int])
+
+ ($.documentation /.template
+ (format "Define macros in the style of with_template."
+ \n "For simple macros that do not need any fancy features.")
+ [(def square
+ (template (square x)
+ (* x x)))])
+
+ ($.documentation /.these
+ (format "Given a (potentially empty) list of codes, just returns them immediately, without any work done."
+ \n "This may seen useless, but it has its utility when dealing with controlled-macro-expansion macros.")
+ [(with_expansions [<operands> (these 1
+ 2
+ 3
+ 4)]
+ (all + <operands>))])
+
+ ($.documentation /.char
+ "If given a 1-character text literal, yields the char-code of the sole character."
+ [(is Nat
+ (char "A"))
+ "=>"
+ 65])
+
+ ($.documentation /.for
+ (format "Selects the appropriate code for a given target-platform when compiling Lux to it."
+ \n "Look-up the available targets in library/lux/target.")
+ [(def js
+ "JavaScript")
+
+ (for "JVM" (do jvm stuff)
+ js (do js stuff)
+ (do default stuff))])
+
+ ($.documentation /.``
+ (format "Delimits a controlled (spliced) macro-expansion."
+ \n "Uses a (~~) special form to specify where to expand.")
+ [(`` (some expression
+ (~~ (some macro which may yield 0 or more results))))])
+
+ ... ($.documentation /.^code
+ ... "Generates pattern-matching code for Code values in a way that looks like code-templating."
+ ... [(is (Maybe Nat)
+ ... (case (` (#0 123 +456.789))
+ ... (^code (#0 (~ [_ {.#Nat number}]) +456.789))
+ ... {.#Some number}
+
+ ... _
+ ... {.#None}))])
+
+ ($.documentation /.false
+ "The boolean FALSE value.")
+
+ ($.documentation /.true
+ "The boolean TRUE value.")
+
+ ($.documentation /.try
+ ""
+ [(is Foo
+ (case (is (Either Text Bar)
+ (try (is Bar
+ (risky computation which may panic))))
+ {.#Right success}
+ (is Foo
+ (do something after success))
+
+ {.#Left error}
+ (is Foo
+ (recover from error))))])
+
+ ($.default (/.Code' w))
+ ($.default /.Alias)
+ ($.default (/.Bindings key value))
+ ($.default /.Ref)
+ ($.default /.Scope)
+ ($.default /.Source)
+ ($.default /.Module_State)
+ ($.default /.Type_Context)
+ ($.default /.Macro')
+ ($.default /.Label)
+ ($.default /.macro)]
+ [/abstract.documentation
+ /control.documentation
+ /data.documentation
+ /debug.documentation
+ /documentation.documentation
+ /extension.documentation
+ /ffi.documentation
+ /locale.documentation
+ /macro.documentation
+ /math.documentation
+ /meta.documentation
+ /program.documentation
+ /static.documentation
+ /target.documentation
+ /test.documentation
+ /time.documentation
+ /tool.documentation
+ /type.documentation
+ /world.documentation])))
(program: inputs
(io.io (debug.log! ($.markdown ..documentation))))
diff --git a/stdlib/source/documentation/lux/abstract.lux b/stdlib/source/documentation/lux/abstract.lux
index 809448aa0..52febba83 100644
--- a/stdlib/source/documentation/lux/abstract.lux
+++ b/stdlib/source/documentation/lux/abstract.lux
@@ -1,10 +1,8 @@
(.require
[library
[lux (.except)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
- [text (.only \n)
- ["%" \\format (.only format)]]
[collection
["[0]" list]]]]]
["[0]" /
diff --git a/stdlib/source/documentation/lux/abstract/apply.lux b/stdlib/source/documentation/lux/abstract/apply.lux
index 7acdd22f7..e14b743f1 100644
--- a/stdlib/source/documentation/lux/abstract/apply.lux
+++ b/stdlib/source/documentation/lux/abstract/apply.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux
- ["$" documentation (.only documentation)]]]
+ ["$" documentation]]]
[\\library
["[0]" /]])
@@ -9,9 +9,9 @@
(.List $.Module)
($.module /._
""
- [(documentation (/.Apply f)
+ [($.documentation (/.Apply f)
"Applicative functors.")
- (documentation /.composite
+ ($.documentation /.composite
"Applicative functor composition.")]
[]))
diff --git a/stdlib/source/documentation/lux/abstract/codec.lux b/stdlib/source/documentation/lux/abstract/codec.lux
index d90b32b19..0bf5a020c 100644
--- a/stdlib/source/documentation/lux/abstract/codec.lux
+++ b/stdlib/source/documentation/lux/abstract/codec.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux
- ["$" documentation (.only documentation)]]]
+ ["$" documentation]]]
[\\library
["[0]" /]])
@@ -9,10 +9,10 @@
(.List $.Module)
($.module /._
""
- [(documentation (/.Codec medium value)
+ [($.documentation (/.Codec medium value)
"A way to move back-and-forth between a type and an alternative representation for it.")
- (documentation /.composite
+ ($.documentation /.composite
"Codec composition."
[(is (Codec c a)
(composite (is (Codec c b)
diff --git a/stdlib/source/documentation/lux/abstract/comonad.lux b/stdlib/source/documentation/lux/abstract/comonad.lux
index d17c0aced..6649be330 100644
--- a/stdlib/source/documentation/lux/abstract/comonad.lux
+++ b/stdlib/source/documentation/lux/abstract/comonad.lux
@@ -1,27 +1,27 @@
(.require
[library
[lux
- ["$" documentation (.only documentation)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]]]
[\\library
["[0]" /]]
["[0]" /
- ["[1][0]" cofree]])
+ ["[1][0]" free]])
(.def .public documentation
(.List $.Module)
($.module /._
""
- [(documentation (/.CoMonad !)
+ [($.documentation (/.CoMonad !)
(format "Co-monads are the opposite/complement to monads."
\n "Co-monadic structures are often infinite in size and built upon lazily-evaluated functions."))
- (documentation /.be
+ ($.documentation /.be
"A co-monadic parallel to the 'do' macro."
[(let [square (function (_ n) (* n n))]
(be comonad
[inputs (iterate ++ +2)]
(square (out inputs))))])]
- [/cofree.documentation]))
+ [/free.documentation]))
diff --git a/stdlib/source/documentation/lux/abstract/comonad/cofree.lux b/stdlib/source/documentation/lux/abstract/comonad/cofree.lux
deleted file mode 100644
index b2c29f49f..000000000
--- a/stdlib/source/documentation/lux/abstract/comonad/cofree.lux
+++ /dev/null
@@ -1,16 +0,0 @@
-(.require
- [library
- [lux
- ["$" documentation (.only documentation)]]]
- [\\library
- ["[0]" /]])
-
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [(documentation (/.CoFree ! it)
- "The CoFree CoMonad.")
- ($.default /.functor)
- ($.default /.comonad)]
- []))
diff --git a/stdlib/source/documentation/lux/abstract/comonad/free.lux b/stdlib/source/documentation/lux/abstract/comonad/free.lux
new file mode 100644
index 000000000..4d37b2953
--- /dev/null
+++ b/stdlib/source/documentation/lux/abstract/comonad/free.lux
@@ -0,0 +1,17 @@
+(.require
+ [library
+ [lux
+ ["$" documentation]]]
+ [\\library
+ ["[0]" /]])
+
+(.def .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [($.default /.functor)
+ ($.default /.comonad)
+
+ ($.documentation (/.Free ! it)
+ "The Free CoMonad.")]
+ []))
diff --git a/stdlib/source/documentation/lux/abstract/enum.lux b/stdlib/source/documentation/lux/abstract/enum.lux
index 4a2ba511b..b6c0aa0a1 100644
--- a/stdlib/source/documentation/lux/abstract/enum.lux
+++ b/stdlib/source/documentation/lux/abstract/enum.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux
- ["$" documentation (.only documentation)]]]
+ ["$" documentation]]]
[\\library
["[0]" /]])
@@ -9,10 +9,10 @@
(.List $.Module)
($.module /._
""
- [(documentation (/.Enum it)
+ [($.documentation (/.Enum it)
"Enumerable types, with a notion of moving forward and backwards through a type's instances.")
- (documentation /.range
+ ($.documentation /.range
"An inclusive [from, to] range of values."
[(range enum from to)])]
[]))
diff --git a/stdlib/source/documentation/lux/abstract/equivalence.lux b/stdlib/source/documentation/lux/abstract/equivalence.lux
index 66ffdf9af..0867832d8 100644
--- a/stdlib/source/documentation/lux/abstract/equivalence.lux
+++ b/stdlib/source/documentation/lux/abstract/equivalence.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux
- ["$" documentation (.only documentation)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]]]
@@ -12,10 +12,10 @@
(.List $.Module)
($.module /._
""
- [(documentation (/.Equivalence it)
+ [($.documentation (/.Equivalence it)
"Equivalence for a type's instances.")
- (documentation /.rec
+ ($.documentation /.rec
"A recursive equivalence combinator."
[(rec recursive_equivalence)])
diff --git a/stdlib/source/documentation/lux/abstract/functor.lux b/stdlib/source/documentation/lux/abstract/functor.lux
index b0521cae1..853b461f8 100644
--- a/stdlib/source/documentation/lux/abstract/functor.lux
+++ b/stdlib/source/documentation/lux/abstract/functor.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]]]
@@ -10,15 +10,6 @@
["[0]" /
["[1][0]" contravariant]])
-(documentation: /.sum
- "Co-product (sum) composition for functors.")
-
-(documentation: /.product
- "Product composition for functors.")
-
-(documentation: /.composite
- "Functor composition.")
-
(.def .public documentation
(.List $.Module)
($.module /._
@@ -27,7 +18,13 @@
($.default (/.Or left right))
($.default (/.And left right))
($.default (/.Then outer inner))
- ..sum
- ..product
- ..composite]
+
+ ($.documentation /.sum
+ "Co-product (sum) composition for functors.")
+
+ ($.documentation /.product
+ "Product composition for functors.")
+
+ ($.documentation /.composite
+ "Functor composition.")]
[/contravariant.documentation]))
diff --git a/stdlib/source/documentation/lux/abstract/functor/contravariant.lux b/stdlib/source/documentation/lux/abstract/functor/contravariant.lux
index 731af9b8e..406934d20 100644
--- a/stdlib/source/documentation/lux/abstract/functor/contravariant.lux
+++ b/stdlib/source/documentation/lux/abstract/functor/contravariant.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux
- ["$" documentation (.only documentation)]]]
+ ["$" documentation]]]
[\\library
["[0]" /]])
@@ -9,6 +9,6 @@
(.List $.Module)
($.module /._
""
- [(documentation (/.Functor !)
+ [($.documentation (/.Functor !)
"The contravariant functor.")]
[]))
diff --git a/stdlib/source/documentation/lux/abstract/hash.lux b/stdlib/source/documentation/lux/abstract/hash.lux
index 04323dcc6..da121864d 100644
--- a/stdlib/source/documentation/lux/abstract/hash.lux
+++ b/stdlib/source/documentation/lux/abstract/hash.lux
@@ -1,20 +1,19 @@
(.require
[library
[lux
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]]]
[\\library
["[0]" /]])
-(documentation: (/.Hash it)
- "A way to produce hash-codes for a type's instances.")
-
(.def .public documentation
(.List $.Module)
($.module /._
""
- [..Hash
- ($.default /.functor)]
+ [($.default /.functor)
+
+ ($.documentation (/.Hash it)
+ "A way to produce hash-codes for a type's instances.")]
[]))
diff --git a/stdlib/source/documentation/lux/abstract/interval.lux b/stdlib/source/documentation/lux/abstract/interval.lux
index a97e137aa..84e20a61f 100644
--- a/stdlib/source/documentation/lux/abstract/interval.lux
+++ b/stdlib/source/documentation/lux/abstract/interval.lux
@@ -1,47 +1,18 @@
(.require
[library
[lux
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]]]
[\\library
["[0]" /]])
-(documentation: (/.Interval it)
- "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.")
-
-(documentation: /.union
- "An interval that spans both predecessors.")
-
-(documentation: /.intersection
- "An interval spanned by both predecessors.")
-
-(documentation: /.complement
- "The inverse of an interval.")
-
-(documentation: /.meets?
- "Whether an interval meets another one on its bottom/lower side.")
-
(.def .public documentation
(.List $.Module)
($.module /._
""
- [..Interval
- ..singleton
- ..borders?
- ..union
- ..intersection
- ..complement
- ..meets?
- ($.default /.between)
+ [($.default /.between)
($.default /.inner?)
($.default /.outer?)
($.default /.singleton?)
@@ -57,5 +28,27 @@
($.default /.finishes?)
($.default /.equivalence)
($.default /.nested?)
- ($.default /.overlaps?)]
+ ($.default /.overlaps?)
+
+ ($.documentation (/.Interval it)
+ "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.")
+
+ ($.documentation /.union
+ "An interval that spans both predecessors.")
+
+ ($.documentation /.intersection
+ "An interval spanned by both predecessors.")
+
+ ($.documentation /.complement
+ "The inverse of an interval.")
+
+ ($.documentation /.meets?
+ "Whether an interval meets another one on its bottom/lower side.")]
[]))
diff --git a/stdlib/source/documentation/lux/abstract/mix.lux b/stdlib/source/documentation/lux/abstract/mix.lux
index 744a5a2ba..d63ebe15a 100644
--- a/stdlib/source/documentation/lux/abstract/mix.lux
+++ b/stdlib/source/documentation/lux/abstract/mix.lux
@@ -1,24 +1,21 @@
(.require
[library
[lux
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]]]
[\\library
["[0]" /]])
-(documentation: (/.Mix structure)
- "Iterate over a structure's values to build a summary value.")
-
-(documentation: /.with_monoid
- "Mix a mixable structure using the monoid's identity as the initial value."
- [(with_monoid monoid mix value)])
-
(.def .public documentation
(.List $.Module)
($.module /._
""
- [..Mix
- ..with_monoid]
+ [($.documentation (/.Mix structure)
+ "Iterate over a structure's values to build a summary value.")
+
+ ($.documentation /.with_monoid
+ "Mix a mixable structure using the monoid's identity as the initial value."
+ [(with_monoid monoid mix value)])]
[]))
diff --git a/stdlib/source/documentation/lux/abstract/monad.lux b/stdlib/source/documentation/lux/abstract/monad.lux
index cff2d9c20..3e160d0fe 100644
--- a/stdlib/source/documentation/lux/abstract/monad.lux
+++ b/stdlib/source/documentation/lux/abstract/monad.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]]]
@@ -10,46 +10,38 @@
["[0]" /
["[1][0]" free]])
-(documentation: (/.Monad it)
- (format "A monad is a monoid in the category of endofunctors."
- \n "What's the problem?"))
-
-(documentation: /.do
- "Macro for easy concatenation of monadic operations."
- [(do monad
- [y (f1 x)
- z (f2 z)]
- (in (f3 z)))])
-
-(documentation: /.then
- "Apply a function with monadic effects to a monadic value and yield a new monadic value."
- [(then monad function)])
-
-(documentation: /.all
- "Run all the monadic values in the list and produce a list of the base values."
- [(all monad)])
-
-(documentation: /.each
- "Apply a monadic function to all values in a list."
- [(each monad function items)])
-
-(documentation: /.only
- "Filter the values in a list with a monadic function."
- [(only monad predicate items)])
-
-(documentation: /.mix
- "Mix a list with a monadic function."
- [(mix monad function initial_value items)])
-
(.def .public documentation
(.List $.Module)
($.module /._
""
- [..Monad
- ..do
- ..then
- ..all
- ..each
- ..only
- ..mix]
+ [($.documentation (/.Monad it)
+ (format "A monad is a monoid in the category of endofunctors."
+ \n "What's the problem?"))
+
+ ($.documentation /.do
+ "Macro for easy concatenation of monadic operations."
+ [(do monad
+ [y (f1 x)
+ z (f2 z)]
+ (in (f3 z)))])
+
+ ($.documentation /.then
+ "Apply a function with monadic effects to a monadic value and yield a new monadic value."
+ [(then monad function)])
+
+ ($.documentation /.all
+ "Run all the monadic values in the list and produce a list of the base values."
+ [(all monad)])
+
+ ($.documentation /.each
+ "Apply a monadic function to all values in a list."
+ [(each monad function items)])
+
+ ($.documentation /.only
+ "Filter the values in a list with a monadic function."
+ [(only monad predicate items)])
+
+ ($.documentation /.mix
+ "Mix a list with a monadic function."
+ [(mix monad function initial_value items)])]
[/free.documentation]))
diff --git a/stdlib/source/documentation/lux/abstract/monad/free.lux b/stdlib/source/documentation/lux/abstract/monad/free.lux
index ff1db175b..421a323c8 100644
--- a/stdlib/source/documentation/lux/abstract/monad/free.lux
+++ b/stdlib/source/documentation/lux/abstract/monad/free.lux
@@ -1,19 +1,18 @@
(.require
[library
[lux
- ["$" documentation (.only documentation:)]]]
+ ["$" documentation]]]
[\\library
["[0]" /]])
-(documentation: (/.Free ! it)
- "The Free Monad.")
-
(.def .public documentation
(.List $.Module)
($.module /._
""
- [..Free
- ($.default /.functor)
+ [($.default /.functor)
($.default /.apply)
- ($.default /.monad)]
+ ($.default /.monad)
+
+ ($.documentation (/.Free ! it)
+ "The Free Monad.")]
[]))
diff --git a/stdlib/source/documentation/lux/abstract/monoid.lux b/stdlib/source/documentation/lux/abstract/monoid.lux
index 92a23f176..6b8dc5bbd 100644
--- a/stdlib/source/documentation/lux/abstract/monoid.lux
+++ b/stdlib/source/documentation/lux/abstract/monoid.lux
@@ -1,21 +1,20 @@
(.require
[library
[lux
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]]]
[\\library
["[0]" /]])
-(documentation: (/.Monoid it)
- (format "A way to compose values."
- \n "Includes an identity value which does not alter any other value when combined with."))
-
(.def .public documentation
(.List $.Module)
($.module /._
""
- [..Monoid
- ($.default /.and)]
+ [($.default /.and)
+
+ ($.documentation (/.Monoid it)
+ (format "A way to compose values."
+ \n "Includes an identity value which does not alter any other value when combined with."))]
[]))
diff --git a/stdlib/source/documentation/lux/abstract/order.lux b/stdlib/source/documentation/lux/abstract/order.lux
index 53556553d..b28945800 100644
--- a/stdlib/source/documentation/lux/abstract/order.lux
+++ b/stdlib/source/documentation/lux/abstract/order.lux
@@ -1,48 +1,40 @@
(.require
[library
[lux
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]]]
[\\library
["[0]" /]])
-(documentation: (/.Order it)
- "A signature for types that possess some sense of ordering among their elements.")
+(.def .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [($.default /.functor)
-(documentation: (/.Comparison it)
- "An arbitrary comparison between two values, with the knowledge of how to order them.")
+ ($.documentation (/.Order it)
+ "A signature for types that possess some sense of ordering among their elements.")
-(documentation: /.<=
- "Less than or equal.")
+ ($.documentation (/.Comparison it)
+ "An arbitrary comparison between two values, with the knowledge of how to order them.")
-(documentation: /.>
- "Greater than.")
+ ($.documentation /.<=
+ "Less than or equal.")
-(documentation: /.>=
- "Greater than or equal.")
+ ($.documentation /.>
+ "Greater than.")
-(documentation: (/.Choice it)
- "A choice comparison between two values, with the knowledge of how to order them.")
+ ($.documentation /.>=
+ "Greater than or equal.")
-(documentation: /.min
- "Minimum.")
+ ($.documentation (/.Choice it)
+ "A choice comparison between two values, with the knowledge of how to order them.")
-(documentation: /.max
- "Maximum.")
+ ($.documentation /.min
+ "Minimum.")
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [..Order
- ..Comparison
- ..<=
- ..>
- ..>=
- ..Choice
- ..min
- ..max
- ($.default /.functor)]
+ ($.documentation /.max
+ "Maximum.")]
[]))
diff --git a/stdlib/source/documentation/lux/abstract/predicate.lux b/stdlib/source/documentation/lux/abstract/predicate.lux
index 8c7ad5daa..e8507ce02 100644
--- a/stdlib/source/documentation/lux/abstract/predicate.lux
+++ b/stdlib/source/documentation/lux/abstract/predicate.lux
@@ -1,50 +1,42 @@
(.require
[library
[lux
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]]]
[\\library
["[0]" /]])
-(documentation: (/.Predicate it)
- "A question that can be asked of a value, yield either false (#0) or true (#1).")
+(.def .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [($.default /.union)
+ ($.default /.intersection)
+ ($.default /.functor)
-(documentation: /.none
- "A predicate that always fails.")
+ ($.documentation (/.Predicate it)
+ "A question that can be asked of a value, yield either false (#0) or true (#1).")
-(documentation: /.or
- "A predicate that meets either predecessor.")
+ ($.documentation /.none
+ "A predicate that always fails.")
-(documentation: /.all
- "A predicate that always succeeds.")
+ ($.documentation /.or
+ "A predicate that meets either predecessor.")
-(documentation: /.and
- "A predicate that meets both predecessors.")
+ ($.documentation /.all
+ "A predicate that always succeeds.")
-(documentation: /.complement
- "The opposite of a predicate.")
+ ($.documentation /.and
+ "A predicate that meets both predecessors.")
-(documentation: /.difference
- "A predicate that meeds 'base', but not 'sub'.")
+ ($.documentation /.complement
+ "The opposite of a predicate.")
-(documentation: /.rec
- "Ties the knot for a recursive predicate.")
+ ($.documentation /.difference
+ "A predicate that meeds 'base', but not 'sub'.")
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [..Predicate
- ..none
- ..or
- ..all
- ..and
- ..complement
- ..difference
- ..rec
- ($.default /.union)
- ($.default /.intersection)
- ($.default /.functor)]
+ ($.documentation /.rec
+ "Ties the knot for a recursive predicate.")]
[]))
diff --git a/stdlib/source/documentation/lux/control/concatenative.lux b/stdlib/source/documentation/lux/control/concatenative.lux
index a09b7681c..2f553ce34 100644
--- a/stdlib/source/documentation/lux/control/concatenative.lux
+++ b/stdlib/source/documentation/lux/control/concatenative.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except if loop left right)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text
["%" \\format (.only format)]]]
@@ -16,253 +16,180 @@
[\\library
["[0]" /]])
-(documentation: /.=>
- "Concatenative function types."
- [(=> [Nat] [Nat])]
- [(All (_ a)
- (-> a (=> [] [a])))]
- [(All (_ t)
- (=> [t] []))]
- [(All (_ a b c)
- (=> [a b c] [b c a]))]
- [(All (_ ,,,0 ,,,1)
- (=> [then (=> ,,,0 ,,,1)
- else (=> ,,,0 ,,,1)]
- ,,,0 [Bit then else] ,,,1))])
-
-(documentation: /.apply
- "A generator for functions that turn arity N functions into arity N concatenative functions."
- [(is (=> [Nat] [Nat])
- ((apply 1) ++))])
-
-(with_template [<arity>]
- [(with_expansions [<name> (template.symbol [/._] ["apply_" <arity>])
- <doc> (template.text ["Lift a function of arity " <arity>
- " into a concatenative function of arity " <arity> "."])]
- (documentation: <name>
- <doc>))]
-
- [1] [2] [3] [4]
- [5] [6] [7] [8]
- )
-
-(documentation: /.push
- "Push a value onto the stack.")
-
-(documentation: /.drop
- "Drop/pop a value from the top of the stack.")
-
-(documentation: /.nip
- "Drop the second-to-last value from the top of the stack.")
-
-(documentation: /.dup
- "Duplicate the top of the stack.")
-
-(documentation: /.swap
- "Swaps the 2 topmost stack values.")
-
-(documentation: /.left_rotation
- "Rotes the 3 topmost stack values to the left.")
-
-(documentation: /.right_rotation
- "Rotes the 3 topmost stack values to the right.")
-
-(documentation: /.&&
- "Groups the 2 topmost stack values as a 2-tuple.")
-
-(documentation: /.left
- "Left-injects the top into sum.")
-
-(documentation: /.right
- "Right-injects the top into sum.")
-
-(with_template [<input> <word> <func>]
- [(`` (documentation: (~~ (template.symbol [/._] [<word>]))
- (~~ (template.text [<func> " for " <input> " arithmetic."]))))]
-
- [Nat n/+ n.+]
- [Nat n/- n.-]
- [Nat n/* n.*]
- [Nat n// n./]
- [Nat n/% n.%]
- [Nat n/= n.=]
- [Nat n/< n.<]
- [Nat n/<= n.<=]
- [Nat n/> n.>]
- [Nat n/>= n.>=]
-
- [Int i/+ i.+]
- [Int i/- i.-]
- [Int i/* i.*]
- [Int i// i./]
- [Int i/% i.%]
- [Int i/= i.=]
- [Int i/< i.<]
- [Int i/<= i.<=]
- [Int i/> i.>]
- [Int i/>= i.>=]
-
- [Rev r/+ r.+]
- [Rev r/- r.-]
- [Rev r/* r.*]
- [Rev r// r./]
- [Rev r/% r.%]
- [Rev r/= r.=]
- [Rev r/< r.<]
- [Rev r/<= r.<=]
- [Rev r/> r.>]
- [Rev r/>= r.>=]
-
- [Frac f/+ f.+]
- [Frac f/- f.-]
- [Frac f/* f.*]
- [Frac f// f./]
- [Frac f/% f.%]
- [Frac f/= f.=]
- [Frac f/< f.<]
- [Frac f/<= f.<=]
- [Frac f/> f.>]
- [Frac f/>= f.>=]
- )
-
-(documentation: /.if
- "If expression."
- [(same? "then"
- (/.value (|>> (push true)
- (push "then")
- (push "else")
- if)))])
-
-(documentation: /.call
- "Executes an anonymous block on the stack.")
-
-(documentation: /.loop
- "Executes a block as a loop until it yields #0 to stop.")
-
-(documentation: /.dip
- "Executes a block on the stack, save for the topmost value.")
-
-(documentation: /.dip_2
- "Executes a block on the stack, save for the 2 topmost values.")
-
-(documentation: /.do
- "Do-while loop expression."
- [(n.= (++ sample)
- (/.value (|>> (push sample)
- (push (push false))
- (push (|>> (push 1) n/+))
- do while)))])
-
-(documentation: /.while
- "While loop expression."
- [(n.= (n.+ distance start)
- (/.value (|>> (push start)
- (push (|>> dup
- (push start) n/-
- (push distance) n/<))
- (push (|>> (push 1) n/+))
- while)))])
-
-(documentation: /.compose
- "Function composition."
- [(n.= (n.+ 2 sample)
- (/.value (|>> (push sample)
- (push (|>> (push 1) n/+))
- (push (|>> (push 1) n/+))
- compose
- call)))])
-
-(documentation: /.partial
- "Partial application."
- [(n.= (n.+ sample sample)
- (/.value (|>> (push sample)
- (push sample)
- (push n/+)
- partial
- call)))])
-
-(documentation: /.when
- "Only execute the block when #1.")
-
-(documentation: /.?
- "Choose the top value when #0 and the second-to-top when #1.")
-
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [..=>
- ..apply
- ..apply_1
- ..apply_2
- ..apply_3
- ..apply_4
- ..apply_5
- ..apply_6
- ..apply_7
- ..apply_8
- ..push
- ..drop
- ..nip
- ..dup
- ..swap
- ..left_rotation
- ..right_rotation
- ..&&
- ..left
- ..right
- ..if
- ..call
- ..loop
- ..dip
- ..dip_2
- ..do
- ..while
- ..compose
- ..partial
- ..when
- ..?
-
- ..n/+
- ..n/-
- ..n/*
- ..n//
- ..n/%
- ..n/=
- ..n/<
- ..n/<=
- ..n/>
- ..n/>=
- ..i/+
- ..i/-
- ..i/*
- ..i//
- ..i/%
- ..i/=
- ..i/<
- ..i/<=
- ..i/>
- ..i/>=
- ..r/+
- ..r/-
- ..r/*
- ..r//
- ..r/%
- ..r/=
- ..r/<
- ..r/<=
- ..r/>
- ..r/>=
- ..f/+
- ..f/-
- ..f/*
- ..f//
- ..f/%
- ..f/=
- ..f/<
- ..f/<=
- ..f/>
- ..f/>=
-
- ($.default /.value)]
- []))
+(`` (.def .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [($.default /.value)
+
+ ($.documentation /.=>
+ "Concatenative function types."
+ [(=> [Nat] [Nat])]
+ [(All (_ a)
+ (-> a (=> [] [a])))]
+ [(All (_ t)
+ (=> [t] []))]
+ [(All (_ a b c)
+ (=> [a b c] [b c a]))]
+ [(All (_ ,,,0 ,,,1)
+ (=> [then (=> ,,,0 ,,,1)
+ else (=> ,,,0 ,,,1)]
+ ,,,0 [Bit then else] ,,,1))])
+
+ ($.documentation /.apply
+ "A generator for functions that turn arity N functions into arity N concatenative functions."
+ [(is (=> [Nat] [Nat])
+ ((apply 1) ++))])
+
+ (~~ (with_template [<arity>]
+ [(with_expansions [<name> (template.symbol [/._] ["apply_" <arity>])
+ <doc> (template.text ["Lift a function of arity " <arity>
+ " into a concatenative function of arity " <arity> "."])]
+ ($.documentation <name>
+ <doc>))]
+
+ [1] [2] [3] [4]
+ [5] [6] [7] [8]
+ ))
+
+ ($.documentation /.push
+ "Push a value onto the stack.")
+
+ ($.documentation /.drop
+ "Drop/pop a value from the top of the stack.")
+
+ ($.documentation /.nip
+ "Drop the second-to-last value from the top of the stack.")
+
+ ($.documentation /.dup
+ "Duplicate the top of the stack.")
+
+ ($.documentation /.swap
+ "Swaps the 2 topmost stack values.")
+
+ ($.documentation /.left_rotation
+ "Rotes the 3 topmost stack values to the left.")
+
+ ($.documentation /.right_rotation
+ "Rotes the 3 topmost stack values to the right.")
+
+ ($.documentation /.&&
+ "Groups the 2 topmost stack values as a 2-tuple.")
+
+ ($.documentation /.left
+ "Left-injects the top into sum.")
+
+ ($.documentation /.right
+ "Right-injects the top into sum.")
+
+ (~~ (with_template [<input> <word> <func>]
+ [(`` ($.documentation (~~ (template.symbol [/._] [<word>]))
+ (~~ (template.text [<func> " for " <input> " arithmetic."]))))]
+
+ [Nat n/+ n.+]
+ [Nat n/- n.-]
+ [Nat n/* n.*]
+ [Nat n// n./]
+ [Nat n/% n.%]
+ [Nat n/= n.=]
+ [Nat n/< n.<]
+ [Nat n/<= n.<=]
+ [Nat n/> n.>]
+ [Nat n/>= n.>=]
+
+ [Int i/+ i.+]
+ [Int i/- i.-]
+ [Int i/* i.*]
+ [Int i// i./]
+ [Int i/% i.%]
+ [Int i/= i.=]
+ [Int i/< i.<]
+ [Int i/<= i.<=]
+ [Int i/> i.>]
+ [Int i/>= i.>=]
+
+ [Rev r/+ r.+]
+ [Rev r/- r.-]
+ [Rev r/* r.*]
+ [Rev r// r./]
+ [Rev r/% r.%]
+ [Rev r/= r.=]
+ [Rev r/< r.<]
+ [Rev r/<= r.<=]
+ [Rev r/> r.>]
+ [Rev r/>= r.>=]
+
+ [Frac f/+ f.+]
+ [Frac f/- f.-]
+ [Frac f/* f.*]
+ [Frac f// f./]
+ [Frac f/% f.%]
+ [Frac f/= f.=]
+ [Frac f/< f.<]
+ [Frac f/<= f.<=]
+ [Frac f/> f.>]
+ [Frac f/>= f.>=]
+ ))
+
+ ($.documentation /.if
+ "If expression."
+ [(same? "then"
+ (/.value (|>> (push true)
+ (push "then")
+ (push "else")
+ if)))])
+
+ ($.documentation /.call
+ "Executes an anonymous block on the stack.")
+
+ ($.documentation /.loop
+ "Executes a block as a loop until it yields #0 to stop.")
+
+ ($.documentation /.dip
+ "Executes a block on the stack, save for the topmost value.")
+
+ ($.documentation /.dip_2
+ "Executes a block on the stack, save for the 2 topmost values.")
+
+ ($.documentation /.do
+ "Do-while loop expression."
+ [(n.= (++ sample)
+ (/.value (|>> (push sample)
+ (push (push false))
+ (push (|>> (push 1) n/+))
+ do while)))])
+
+ ($.documentation /.while
+ "While loop expression."
+ [(n.= (n.+ distance start)
+ (/.value (|>> (push start)
+ (push (|>> dup
+ (push start) n/-
+ (push distance) n/<))
+ (push (|>> (push 1) n/+))
+ while)))])
+
+ ($.documentation /.compose
+ "Function composition."
+ [(n.= (n.+ 2 sample)
+ (/.value (|>> (push sample)
+ (push (|>> (push 1) n/+))
+ (push (|>> (push 1) n/+))
+ compose
+ call)))])
+
+ ($.documentation /.partial
+ "Partial application."
+ [(n.= (n.+ sample sample)
+ (/.value (|>> (push sample)
+ (push sample)
+ (push n/+)
+ partial
+ call)))])
+
+ ($.documentation /.when
+ "Only execute the block when #1.")
+
+ ($.documentation /.?
+ "Choose the top value when #0 and the second-to-top when #1.")]
+ [])))
diff --git a/stdlib/source/documentation/lux/control/concurrency.lux b/stdlib/source/documentation/lux/control/concurrency.lux
index ffd314948..3a464a384 100644
--- a/stdlib/source/documentation/lux/control/concurrency.lux
+++ b/stdlib/source/documentation/lux/control/concurrency.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]
diff --git a/stdlib/source/documentation/lux/control/concurrency/actor.lux b/stdlib/source/documentation/lux/control/concurrency/actor.lux
index 27086e8b3..fd52ab040 100644
--- a/stdlib/source/documentation/lux/control/concurrency/actor.lux
+++ b/stdlib/source/documentation/lux/control/concurrency/actor.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except if loop)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,67 +10,54 @@
[\\library
["[0]" /]])
-(documentation: (/.Actor state)
- "An entity that can react to messages (mail) sent to it concurrently.")
+(.def .public documentation
+ (.List $.Module)
+ ($.module /._
+ "The actor model of concurrency."
+ [($.default /.poisoned)
+ ($.default /.dead)
+ ($.default /.alive?)
+ ($.default /.obituary')
-(documentation: (/.Mail state)
- "A one-way message sent to an actor, without expecting a reply.")
+ ($.documentation (/.Actor state)
+ "An entity that can react to messages (mail) sent to it concurrently.")
-(documentation: (/.Obituary state)
- "Details on the death of an actor.")
+ ($.documentation (/.Mail state)
+ "A one-way message sent to an actor, without expecting a reply.")
-(documentation: (/.Behavior state)
- "An actor's behavior when mail is received.")
+ ($.documentation (/.Obituary state)
+ "Details on the death of an actor.")
-(documentation: /.spawn!
- "Given a behavior and initial state, spawns an actor and returns it.")
+ ($.documentation (/.Behavior state)
+ "An actor's behavior when mail is received.")
-(documentation: /.obituary
- "Await for an actor to stop working.")
+ ($.documentation /.spawn!
+ "Given a behavior and initial state, spawns an actor and returns it.")
-(documentation: /.mail!
- "Send mail to an actor.")
+ ($.documentation /.obituary
+ "Await for an actor to stop working.")
-(documentation: (/.Message state output)
- "A two-way message sent to an actor, expecting a reply.")
+ ($.documentation /.mail!
+ "Send mail to an actor.")
-(documentation: /.tell!
- "Communicate with an actor through message-passing.")
+ ($.documentation (/.Message state output)
+ "A two-way message sent to an actor, expecting a reply.")
-(documentation: /.default
- "Default actor behavior.")
+ ($.documentation /.tell!
+ "Communicate with an actor through message-passing.")
-(documentation: /.poison!
- (format "Kills the actor by sending mail that will kill it upon processing,"
- \n "but allows the actor to handle previous mail."))
+ ($.documentation /.default
+ "Default actor behavior.")
-(documentation: /.Stop
- "A signal to stop an actor from observing a channel.")
+ ($.documentation /.poison!
+ (format "Kills the actor by sending mail that will kill it upon processing,"
+ \n "but allows the actor to handle previous mail."))
-(documentation: /.observe!
- (format "Use an actor to observe a channel by transforming each datum"
- \n "flowing through the channel into mail the actor can process."
- \n "Can stop observing the channel by executing the Stop value."))
+ ($.documentation /.Stop
+ "A signal to stop an actor from observing a channel.")
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- "The actor model of concurrency."
- [..Actor
- ..Mail
- ..Obituary
- ..Behavior
- ..spawn!
- ..obituary
- ..mail!
- ..Message
- ..tell!
- ..default
- ..poison!
- ..Stop
- ..observe!
- ($.default /.poisoned)
- ($.default /.dead)
- ($.default /.alive?)
- ($.default /.obituary')]
+ ($.documentation /.observe!
+ (format "Use an actor to observe a channel by transforming each datum"
+ \n "flowing through the channel into mail the actor can process."
+ \n "Can stop observing the channel by executing the Stop value."))]
[]))
diff --git a/stdlib/source/documentation/lux/control/concurrency/async.lux b/stdlib/source/documentation/lux/control/concurrency/async.lux
index 37f5fd09e..6f43db6f6 100644
--- a/stdlib/source/documentation/lux/control/concurrency/async.lux
+++ b/stdlib/source/documentation/lux/control/concurrency/async.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except or and)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,87 +10,72 @@
[\\library
["[0]" /]])
-(documentation: (/.Async it)
- "Represents values produced by asynchronous computations (unlike IO, which is synchronous).")
+(.def .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [($.default /.functor)
+ ($.default /.apply)
+ ($.default /.monad)
-(documentation: (/.Resolver it)
- (format "The function used to give a value to an async."
- \n "Will signal 'true' if the async has been resolved for the 1st time, 'false' otherwise."))
+ ($.documentation (/.Async it)
+ "Represents values produced by asynchronous computations (unlike IO, which is synchronous).")
-(documentation: /.resolved
- "Produces an async that has already been resolved to the given value."
- [(resolved value)])
+ ($.documentation (/.Resolver it)
+ (format "The function used to give a value to an async."
+ \n "Will signal 'true' if the async has been resolved for the 1st time, 'false' otherwise."))
-(documentation: /.async
- "Creates a fresh async that has not been resolved yet."
- [(async _)])
+ ($.documentation /.resolved
+ "Produces an async that has already been resolved to the given value."
+ [(resolved value)])
-(documentation: /.value
- "Polls an async for its value.")
+ ($.documentation /.async
+ "Creates a fresh async that has not been resolved yet."
+ [(async _)])
-(documentation: /.upon!
- "Executes the given function as soon as the async has been resolved."
- [(upon! function async)])
+ ($.documentation /.value
+ "Polls an async for its value.")
-(documentation: /.resolved?
- "Checks whether an async's value has already been resolved.")
+ ($.documentation /.upon!
+ "Executes the given function as soon as the async has been resolved."
+ [(upon! function async)])
-(documentation: /.and
- "Combines the results of both asyncs, in-order."
- [(and left right)])
+ ($.documentation /.resolved?
+ "Checks whether an async's value has already been resolved.")
-(documentation: /.or
- (format "Yields the results of whichever async gets resolved first."
- \n "You can tell which one was resolved first through pattern-matching.")
- [(or left right)])
+ ($.documentation /.and
+ "Combines the results of both asyncs, in-order."
+ [(and left right)])
-(documentation: /.either
- (format "Yields the results of whichever async gets resolved first."
- \n "You cannot tell which one was resolved first.")
- [(either left right)])
+ ($.documentation /.or
+ (format "Yields the results of whichever async gets resolved first."
+ \n "You can tell which one was resolved first through pattern-matching.")
+ [(or left right)])
-(documentation: /.schedule!
- (format "Runs an I/O computation on its own thread (after a specified delay)."
- \n "Returns an async that will eventually host its result.")
- [(schedule! milli_seconds computation)])
+ ($.documentation /.either
+ (format "Yields the results of whichever async gets resolved first."
+ \n "You cannot tell which one was resolved first.")
+ [(either left right)])
-(documentation: /.future
- (format "Runs an I/O computation on its own thread."
- \n "Returns an async that will eventually host its result.")
- [(future computation)])
+ ($.documentation /.schedule!
+ (format "Runs an I/O computation on its own thread (after a specified delay)."
+ \n "Returns an async that will eventually host its result.")
+ [(schedule! milli_seconds computation)])
-(documentation: /.after
- "Delivers a value after a certain period has passed."
- [(after milli_seconds value)])
+ ($.documentation /.future
+ (format "Runs an I/O computation on its own thread."
+ \n "Returns an async that will eventually host its result.")
+ [(future computation)])
-(documentation: /.delay
- "An async that will be resolved after the specified amount of milli-seconds."
- [(delay milli_seconds)])
+ ($.documentation /.after
+ "Delivers a value after a certain period has passed."
+ [(after milli_seconds value)])
-(documentation: /.within
- "Wait for an async to be resolved within the specified amount of milli-seconds."
- [(within milli_seconds async)])
+ ($.documentation /.delay
+ "An async that will be resolved after the specified amount of milli-seconds."
+ [(delay milli_seconds)])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [..Async
- ..Resolver
- ..resolved
- ..async
- ..value
- ..upon!
- ..resolved?
- ..and
- ..or
- ..either
- ..schedule!
- ..future
- ..after
- ..delay
- ..within
- ($.default /.functor)
- ($.default /.apply)
- ($.default /.monad)]
+ ($.documentation /.within
+ "Wait for an async to be resolved within the specified amount of milli-seconds."
+ [(within milli_seconds async)])]
[]))
diff --git a/stdlib/source/documentation/lux/control/concurrency/atom.lux b/stdlib/source/documentation/lux/control/concurrency/atom.lux
index 054876501..5c39f27d5 100644
--- a/stdlib/source/documentation/lux/control/concurrency/atom.lux
+++ b/stdlib/source/documentation/lux/control/concurrency/atom.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except if loop)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,30 +10,26 @@
[\\library
["[0]" /]])
-(documentation: (/.Atom it)
- "Atomic references that are safe to mutate concurrently.")
-
-(documentation: /.compare_and_swap!
- (format "Only mutates an atom if you can present its current value."
- \n "That guarantees that atom was not updated since you last read from it."))
-
-(documentation: /.update!
- (format "Updates an atom by applying a function to its current value."
- \n "If it fails to update it (because some other process wrote to it first), it will retry until it succeeds."
- \n "The retries will be done with the new values of the atom, as they show up."))
-
-(documentation: /.write!
- (format "Writes the given value to an atom."
- \n "If it fails to write it (because some other process wrote to it first), it will retry until it succeeds."))
-
(.def .public documentation
(.List $.Module)
($.module /._
""
- [..Atom
- ..compare_and_swap!
- ..update!
- ..write!
- ($.default /.atom)
- ($.default /.read!)]
+ [($.default /.atom)
+ ($.default /.read!)
+
+ ($.documentation (/.Atom it)
+ "Atomic references that are safe to mutate concurrently.")
+
+ ($.documentation /.compare_and_swap!
+ (format "Only mutates an atom if you can present its current value."
+ \n "That guarantees that atom was not updated since you last read from it."))
+
+ ($.documentation /.update!
+ (format "Updates an atom by applying a function to its current value."
+ \n "If it fails to update it (because some other process wrote to it first), it will retry until it succeeds."
+ \n "The retries will be done with the new values of the atom, as they show up."))
+
+ ($.documentation /.write!
+ (format "Writes the given value to an atom."
+ \n "If it fails to write it (because some other process wrote to it first), it will retry until it succeeds."))]
[]))
diff --git a/stdlib/source/documentation/lux/control/concurrency/frp.lux b/stdlib/source/documentation/lux/control/concurrency/frp.lux
index 9c11eb6d2..ad35eba37 100644
--- a/stdlib/source/documentation/lux/control/concurrency/frp.lux
+++ b/stdlib/source/documentation/lux/control/concurrency/frp.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except if loop)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,49 +10,11 @@
[\\library
["[0]" /]])
-(documentation: (/.Channel it)
- "An asynchronous channel to distribute values.")
-
-(documentation: (/.Sink it)
- "The tail-end of a channel, which can be written-to to fee the channel.")
-
-(documentation: /.channel
- "Creates a brand-new channel and hands it over, along with the sink to write to it."
- [(channel _)])
-
-(documentation: (/.Subscriber it)
- "A function that can receive every value fed into a channel.")
-
-(documentation: /.only
- (format "Produces a new channel based on the old one, only with values"
- \n "that pass the test.")
- [(only pass? channel)])
-
-(documentation: /.of_async
- "A one-element channel containing the output from an async."
- [(of_async async)])
-
-(documentation: /.mix
- "Asynchronous mix over channels."
- [(mix f init channel)])
-
-(documentation: /.sequential
- "Transforms the given list into a channel with the same elements."
- [(sequential milli_seconds values)])
-
(.def .public documentation
(.List $.Module)
($.module /._
""
- [..Channel
- ..Sink
- ..channel
- ..Subscriber
- ..only
- ..of_async
- ..mix
- ..sequential
- ($.default /.channel_is_already_closed)
+ [($.default /.channel_is_already_closed)
($.default /.functor)
($.default /.apply)
($.default /.monad)
@@ -62,5 +24,35 @@
($.default /.periodic)
($.default /.iterations)
($.default /.distinct)
- ($.default /.list)]
+ ($.default /.list)
+
+ ($.documentation (/.Channel it)
+ "An asynchronous channel to distribute values.")
+
+ ($.documentation (/.Sink it)
+ "The tail-end of a channel, which can be written-to to fee the channel.")
+
+ ($.documentation /.channel
+ "Creates a brand-new channel and hands it over, along with the sink to write to it."
+ [(channel _)])
+
+ ($.documentation (/.Subscriber it)
+ "A function that can receive every value fed into a channel.")
+
+ ($.documentation /.only
+ (format "Produces a new channel based on the old one, only with values"
+ \n "that pass the test.")
+ [(only pass? channel)])
+
+ ($.documentation /.of_async
+ "A one-element channel containing the output from an async."
+ [(of_async async)])
+
+ ($.documentation /.mix
+ "Asynchronous mix over channels."
+ [(mix f init channel)])
+
+ ($.documentation /.sequential
+ "Transforms the given list into a channel with the same elements."
+ [(sequential milli_seconds values)])]
[]))
diff --git a/stdlib/source/documentation/lux/control/concurrency/semaphore.lux b/stdlib/source/documentation/lux/control/concurrency/semaphore.lux
index 474144fff..91397cb83 100644
--- a/stdlib/source/documentation/lux/control/concurrency/semaphore.lux
+++ b/stdlib/source/documentation/lux/control/concurrency/semaphore.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except if loop)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,60 +10,49 @@
[\\library
["[0]" /]])
-(documentation: /.Semaphore
- "A tool for controlling access to resources by multiple concurrent processes.")
+(.def .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [($.default /.semaphore_is_maxed_out)
+ ($.default /.barrier)
-(documentation: /.semaphore
- ""
- [(semaphore initial_open_positions)])
+ ($.documentation /.Semaphore
+ "A tool for controlling access to resources by multiple concurrent processes.")
-(documentation: /.wait!
- (format "Wait on a semaphore until there are open positions."
- \n "After finishing your work, you must 'signal' to the semaphore that you're done.")
- [(wait! semaphore)])
+ ($.documentation /.semaphore
+ ""
+ [(semaphore initial_open_positions)])
-(documentation: /.signal!
- "Signal to a semaphore that you're done with your work, and that there is a new open position."
- [(signal! semaphore)])
+ ($.documentation /.wait!
+ (format "Wait on a semaphore until there are open positions."
+ \n "After finishing your work, you must 'signal' to the semaphore that you're done.")
+ [(wait! semaphore)])
-(documentation: /.Mutex
- "A mutual-exclusion lock that can only be acquired by one process at a time.")
+ ($.documentation /.signal!
+ "Signal to a semaphore that you're done with your work, and that there is a new open position."
+ [(signal! semaphore)])
-(documentation: /.mutex
- "Creates a brand-new mutex."
- [(mutex _)])
+ ($.documentation /.Mutex
+ "A mutual-exclusion lock that can only be acquired by one process at a time.")
-(documentation: /.synchronize!
- "Runs the procedure with exclusive control of the mutex."
- [(synchronize! mutex procedure)])
+ ($.documentation /.mutex
+ "Creates a brand-new mutex."
+ [(mutex _)])
-(documentation: /.limit
- "Produce a limit for a barrier.")
+ ($.documentation /.synchronize!
+ "Runs the procedure with exclusive control of the mutex."
+ [(synchronize! mutex procedure)])
-(documentation: /.Limit
- "A limit for barriers.")
+ ($.documentation /.limit
+ "Produce a limit for a barrier.")
-(documentation: /.Barrier
- "A barrier that blocks all processes from proceeding until a given number of processes are parked at the barrier.")
+ ($.documentation /.Limit
+ "A limit for barriers.")
-(documentation: /.block!
- "Wait on a barrier until all processes have arrived and met the barrier's limit.")
+ ($.documentation /.Barrier
+ "A barrier that blocks all processes from proceeding until a given number of processes are parked at the barrier.")
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [..Semaphore
- ..semaphore
- ..wait!
- ..signal!
- ..Mutex
- ..mutex
- ..synchronize!
- ..limit
- ..Limit
- ..Barrier
- ..block!
- ($.default /.semaphore_is_maxed_out)
- ($.default /.barrier)]
+ ($.documentation /.block!
+ "Wait on a barrier until all processes have arrived and met the barrier's limit.")]
[]))
diff --git a/stdlib/source/documentation/lux/control/concurrency/stm.lux b/stdlib/source/documentation/lux/control/concurrency/stm.lux
index 000afb6e0..d3e03d8fd 100644
--- a/stdlib/source/documentation/lux/control/concurrency/stm.lux
+++ b/stdlib/source/documentation/lux/control/concurrency/stm.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except if loop)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,43 +10,37 @@
[\\library
["[0]" /]])
-(documentation: (/.Var it)
- "A mutable cell containing a value, and observers that will be alerted of any change to it.")
-
-(documentation: /.var
- "Creates a new STM var, with a default value."
- [(var value)])
-
-(documentation: /.changes
- "Creates a channel that will receive all changes to the value of the given var."
- [(changes target)])
-
-(documentation: (/.STM it)
- "A computation which updates a transaction and produces a value.")
-
-(documentation: /.update
- "Update a var's value, and return a tuple with the old and the new values."
- [(update function var)])
-
-(documentation: /.commit!
- (format "Commits a transaction and returns its result (asynchronously)."
- \n "Note that a transaction may be re-run an indeterminate number of times if other transactions involving the same variables successfully commit first."
- \n "For this reason, it's important to note that transactions must be free from side-effects, such as I/O.")
- [(commit! procedure)])
-
(.def .public documentation
(.List $.Module)
($.module /._
""
- [..Var
- ..var
- ..changes
- ..STM
- ..update
- ..commit!
- ($.default /.read)
+ [($.default /.read)
($.default /.write)
($.default /.functor)
($.default /.apply)
- ($.default /.monad)]
+ ($.default /.monad)
+
+ ($.documentation (/.Var it)
+ "A mutable cell containing a value, and observers that will be alerted of any change to it.")
+
+ ($.documentation /.var
+ "Creates a new STM var, with a default value."
+ [(var value)])
+
+ ($.documentation /.changes
+ "Creates a channel that will receive all changes to the value of the given var."
+ [(changes target)])
+
+ ($.documentation (/.STM it)
+ "A computation which updates a transaction and produces a value.")
+
+ ($.documentation /.update
+ "Update a var's value, and return a tuple with the old and the new values."
+ [(update function var)])
+
+ ($.documentation /.commit!
+ (format "Commits a transaction and returns its result (asynchronously)."
+ \n "Note that a transaction may be re-run an indeterminate number of times if other transactions involving the same variables successfully commit first."
+ \n "For this reason, it's important to note that transactions must be free from side-effects, such as I/O.")
+ [(commit! procedure)])]
[]))
diff --git a/stdlib/source/documentation/lux/control/concurrency/thread.lux b/stdlib/source/documentation/lux/control/concurrency/thread.lux
index c4dbf2408..b0206bc6c 100644
--- a/stdlib/source/documentation/lux/control/concurrency/thread.lux
+++ b/stdlib/source/documentation/lux/control/concurrency/thread.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except if loop)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,17 +10,14 @@
[\\library
["[0]" /]])
-(documentation: /.parallelism
- "How many processes can run in parallel.")
-
-(documentation: /.schedule!
- "Executes an I/O procedure after some milli-seconds."
- [(schedule! milli_seconds action)])
-
(.def .public documentation
(.List $.Module)
($.module /._
""
- [..parallelism
- ..schedule!]
+ [($.documentation /.parallelism
+ "How many processes can run in parallel.")
+
+ ($.documentation /.schedule!
+ "Executes an I/O procedure after some milli-seconds."
+ [(schedule! milli_seconds action)])]
[]))
diff --git a/stdlib/source/documentation/lux/control/continuation.lux b/stdlib/source/documentation/lux/control/continuation.lux
index 0c165a0d4..4cadaecc7 100644
--- a/stdlib/source/documentation/lux/control/continuation.lux
+++ b/stdlib/source/documentation/lux/control/continuation.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except if loop)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,44 +10,39 @@
[\\library
["[0]" /]])
-(documentation: (/.Cont input output)
- "Continuations.")
-
-(documentation: /.continued
- "Continues a continuation thunk."
- [(continued next cont)])
-
-(documentation: /.result
- "Forces a continuation thunk to be evaluated."
- [(result cont)])
-
-(documentation: /.with_current
- "Call with current continuation."
- [(with_current
- (function (_ go)
- (do /.monad
- [.let [nexus (function (nexus val)
- (go [nexus val]))]
- _ (go [nexus init])]
- (in (undefined)))))])
-
-(documentation: /.pending
- "Turns any expression into a function that is pending a continuation."
- [(pending (some_function some_input))])
-
(.def .public documentation
(.List $.Module)
($.module /._
""
- [..Cont
- ..continued
- ..result
- ..with_current
- ..pending
- ($.default /.reset)
+ [($.default /.reset)
($.default /.shift)
($.default /.functor)
($.default /.apply)
($.default /.monad)
- ($.default /.portal)]
+ ($.default /.portal)
+
+ ($.documentation (/.Cont input output)
+ "Continuations.")
+
+ ($.documentation /.continued
+ "Continues a continuation thunk."
+ [(continued next cont)])
+
+ ($.documentation /.result
+ "Forces a continuation thunk to be evaluated."
+ [(result cont)])
+
+ ($.documentation /.with_current
+ "Call with current continuation."
+ [(with_current
+ (function (_ go)
+ (do /.monad
+ [.let [nexus (function (nexus val)
+ (go [nexus val]))]
+ _ (go [nexus init])]
+ (in (undefined)))))])
+
+ ($.documentation /.pending
+ "Turns any expression into a function that is pending a continuation."
+ [(pending (some_function some_input))])]
[]))
diff --git a/stdlib/source/documentation/lux/control/exception.lux b/stdlib/source/documentation/lux/control/exception.lux
index f0936e27e..b74a152fe 100644
--- a/stdlib/source/documentation/lux/control/exception.lux
+++ b/stdlib/source/documentation/lux/control/exception.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except if loop)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,70 +10,60 @@
[\\library
["[0]" /]])
-(documentation: (/.Exception it)
- "An exception provides a way to decorate error messages.")
+(.def .public documentation
+ (.List $.Module)
+ ($.module /._
+ "Pure-Lux exception-handling functionality."
+ [($.default /.assertion)
-(documentation: /.match?
- "Is this exception the cause of the error message?"
- [(match? exception error)])
+ ($.documentation (/.Exception it)
+ "An exception provides a way to decorate error messages.")
-(documentation: /.when
- (format "If a particular exception is detected on a possibly-erroneous value, handle it."
- \n "If no exception was detected, or a different one from the one being checked, then pass along the original value.")
- [(when exception then try)])
+ ($.documentation /.match?
+ "Is this exception the cause of the error message?"
+ [(match? exception error)])
-(documentation: /.otherwise
- "If no handler could be found to catch the exception, then run a function as a last-resort measure."
- [(otherwise else try)])
+ ($.documentation /.when
+ (format "If a particular exception is detected on a possibly-erroneous value, handle it."
+ \n "If no exception was detected, or a different one from the one being checked, then pass along the original value.")
+ [(when exception then try)])
-(documentation: /.error
- "Constructs an error message from an exception."
- [(error exception message)])
+ ($.documentation /.otherwise
+ "If no handler could be found to catch the exception, then run a function as a last-resort measure."
+ [(otherwise else try)])
-(documentation: /.except
- "Decorate an error message with an Exception and lift it into the error-handling context."
- [(except exception message)])
+ ($.documentation /.error
+ "Constructs an error message from an exception."
+ [(error exception message)])
-(documentation: /.exception
- (format "Define a new exception type."
- \n "It mostly just serves as a way to tag error messages for later catching.")
- ["Simple case:"
- (exception .public some_exception)]
- ["Complex case:"
- (exception .public [arbitrary type variables] (some_exception [optional Text
- arguments Int])
- optional_body)])
+ ($.documentation /.except
+ "Decorate an error message with an Exception and lift it into the error-handling context."
+ [(except exception message)])
-(documentation: /.report
- "An error report."
- [(is Text
- (report ["Row 0" value/0]
- ["Row 1" value/1]
- ,,,
- ["Row N" value/N]))])
+ ($.documentation /.exception
+ (format "Define a new exception type."
+ \n "It mostly just serves as a way to tag error messages for later catching.")
+ ["Simple case:"
+ (exception .public some_exception)]
+ ["Complex case:"
+ (exception .public [arbitrary type variables] (some_exception [optional Text
+ arguments Int])
+ optional_body)])
-(documentation: /.listing
- (format "A numbered report of the entries on a list."
- \n "NOTE: 0-based numbering.")
- [(listing format entries)])
+ ($.documentation /.report
+ "An error report."
+ [(is Text
+ (report ["Row 0" value/0]
+ ["Row 1" value/1]
+ ,,,
+ ["Row N" value/N]))])
-(documentation: /.with
- "If a computation fails, prepends the exception to the error."
- [(with exception message computation)])
+ ($.documentation /.listing
+ (format "A numbered report of the entries on a list."
+ \n "NOTE: 0-based numbering.")
+ [(listing format entries)])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- "Pure-Lux exception-handling functionality."
- [..Exception
- ..match?
- ..when
- ..otherwise
- ..error
- ..except
- ..exception
- ..report
- ..listing
- ..with
- ($.default /.assertion)]
+ ($.documentation /.with
+ "If a computation fails, prepends the exception to the error."
+ [(with exception message computation)])]
[]))
diff --git a/stdlib/source/documentation/lux/control/function.lux b/stdlib/source/documentation/lux/control/function.lux
index 4a0566eca..4d73ff69b 100644
--- a/stdlib/source/documentation/lux/control/function.lux
+++ b/stdlib/source/documentation/lux/control/function.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except if loop)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -15,41 +15,36 @@
["[1][0]" mixin]
["[1][0]" mutual]])
-(documentation: /.identity
- (format "Identity function."
- \n "Does nothing to its argument and just returns it.")
- [(same? (identity value)
- value)])
+(.def .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [($.default /.monoid)
-(documentation: /.composite
- "Function composition."
- [(= ((composite f g) "foo")
- (f (g "foo")))])
+ ($.documentation /.identity
+ (format "Identity function."
+ \n "Does nothing to its argument and just returns it.")
+ [(same? (identity value)
+ value)])
-(documentation: /.constant
- "Create constant functions."
- [(= ((constant "foo") "bar")
- "foo")])
+ ($.documentation /.composite
+ "Function composition."
+ [(= ((composite f g) "foo")
+ (f (g "foo")))])
-(documentation: /.flipped
- "Flips the order of the arguments of a function."
- [(= ((flipped f) "foo" "bar")
- (f "bar" "foo"))])
+ ($.documentation /.constant
+ "Create constant functions."
+ [(= ((constant "foo") "bar")
+ "foo")])
-(documentation: /.on
- "Simple 1-argument function application."
- [(on input function)])
+ ($.documentation /.flipped
+ "Flips the order of the arguments of a function."
+ [(= ((flipped f) "foo" "bar")
+ (f "bar" "foo"))])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [..identity
- ..composite
- ..constant
- ..flipped
- ..on
- ($.default /.monoid)]
+ ($.documentation /.on
+ "Simple 1-argument function application."
+ [(on input function)])]
[/contract.documentation
/memo.documentation
/mixin.documentation
diff --git a/stdlib/source/documentation/lux/control/function/contract.lux b/stdlib/source/documentation/lux/control/function/contract.lux
index 9545d94e2..d1a24154f 100644
--- a/stdlib/source/documentation/lux/control/function/contract.lux
+++ b/stdlib/source/documentation/lux/control/function/contract.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except if loop)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,27 +10,25 @@
[\\library
["[0]" /]])
-(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)]
+ [($.default /.pre_condition_failed)
+ ($.default /.post_condition_failed)
+
+ ($.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))])]
[]))
diff --git a/stdlib/source/documentation/lux/control/function/memo.lux b/stdlib/source/documentation/lux/control/function/memo.lux
index 9699fccee..6b78db63e 100644
--- a/stdlib/source/documentation/lux/control/function/memo.lux
+++ b/stdlib/source/documentation/lux/control/function/memo.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except open)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,27 +10,24 @@
[\\library
["[0]" /]])
-(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 input output))]
+ [($.default /.memoization)
+ ($.default (/.Memo input output))
+
+ ($.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)])]
[]))
diff --git a/stdlib/source/documentation/lux/control/function/mixin.lux b/stdlib/source/documentation/lux/control/function/mixin.lux
index 96bbb9756..7f05a4502 100644
--- a/stdlib/source/documentation/lux/control/function/mixin.lux
+++ b/stdlib/source/documentation/lux/control/function/mixin.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except if loop)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,51 +10,42 @@
[\\library
["[0]" /]])
-(documentation: (/.Mixin input output)
- "A partially-defined function which can be mixed with others to inherit their behavior.")
+(.def .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [($.default /.monoid)
-(documentation: /.fixed
- "Given a mixin, produces a normal function."
- [(fixed f)])
+ ($.documentation (/.Mixin input output)
+ "A partially-defined function which can be mixed with others to inherit their behavior.")
-(documentation: /.nothing
- "A mixin that does nothing and just delegates work to the next mixin.")
+ ($.documentation /.fixed
+ "Given a mixin, produces a normal function."
+ [(fixed f)])
-(documentation: /.mixed
- "Produces a new mixin, where the behavior of the child can make use of the behavior of the parent."
- [(mixed parent child)])
+ ($.documentation /.nothing
+ "A mixin that does nothing and just delegates work to the next mixin.")
-(documentation: /.advice
- "Only apply then mixin when the input meets some criterion."
- [(advice when then)])
+ ($.documentation /.mixed
+ "Produces a new mixin, where the behavior of the child can make use of the behavior of the parent."
+ [(mixed parent child)])
-(documentation: /.before
- "Executes an action before doing the main work."
- [(before monad action)])
+ ($.documentation /.advice
+ "Only apply then mixin when the input meets some criterion."
+ [(advice when then)])
-(documentation: /.after
- "Executes an action after doing the main work."
- [(after monad action)])
+ ($.documentation /.before
+ "Executes an action before doing the main work."
+ [(before monad action)])
-(documentation: (/.Recursive input output)
- "An indirectly recursive function.")
+ ($.documentation /.after
+ "Executes an action after doing the main work."
+ [(after monad action)])
-(documentation: /.of_recursive
- "Transform an indirectly recursive function into a mixin."
- [(of_recursive recursive)])
+ ($.documentation (/.Recursive input output)
+ "An indirectly recursive function.")
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [..Mixin
- ..fixed
- ..nothing
- ..mixed
- ..advice
- ..before
- ..after
- ..Recursive
- ..of_recursive
- ($.default /.monoid)]
+ ($.documentation /.of_recursive
+ "Transform an indirectly recursive function into a mixin."
+ [(of_recursive recursive)])]
[]))
diff --git a/stdlib/source/documentation/lux/control/function/mutual.lux b/stdlib/source/documentation/lux/control/function/mutual.lux
index 57cf0d2f3..96208e936 100644
--- a/stdlib/source/documentation/lux/control/function/mutual.lux
+++ b/stdlib/source/documentation/lux/control/function/mutual.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except let def)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,41 +10,38 @@
[\\library
["[0]" /]])
-(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]
+ [($.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)))])])]
[]))
diff --git a/stdlib/source/documentation/lux/control/io.lux b/stdlib/source/documentation/lux/control/io.lux
index ff76f1396..495f57023 100644
--- a/stdlib/source/documentation/lux/control/io.lux
+++ b/stdlib/source/documentation/lux/control/io.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except if loop)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,27 +10,24 @@
[\\library
["[0]" /]])
-(documentation: (/.IO it)
- "A type that represents synchronous, effectful computations that may interact with the outside world.")
-
-(documentation: /.io
- (format "Delays the evaluation of an expression, by wrapping it in an IO 'thunk'."
- \n "Great for wrapping effectful computations (which will not be performed until the IO is 'run!').")
- [(io (exec
- (log! msg)
- "Some value..."))])
-
-(documentation: /.run!
- "A way to execute IO computations and perform their side-effects.")
-
(.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!
- ($.default /.functor)
+ [($.default /.functor)
($.default /.apply)
- ($.default /.monad)]
+ ($.default /.monad)
+
+ ($.documentation (/.IO it)
+ "A type that represents synchronous, effectful computations that may interact with the outside world.")
+
+ ($.documentation /.io
+ (format "Delays the evaluation of an expression, by wrapping it in an IO 'thunk'."
+ \n "Great for wrapping effectful computations (which will not be performed until the IO is 'run!').")
+ [(io (exec
+ (log! msg)
+ "Some value..."))])
+
+ ($.documentation /.run!
+ "A way to execute IO computations and perform their side-effects.")]
[]))
diff --git a/stdlib/source/documentation/lux/control/lazy.lux b/stdlib/source/documentation/lux/control/lazy.lux
index 2476283ff..ddf543f5d 100644
--- a/stdlib/source/documentation/lux/control/lazy.lux
+++ b/stdlib/source/documentation/lux/control/lazy.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except if loop)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,23 +10,21 @@
[\\library
["[0]" /]])
-(documentation: (/.Lazy it)
- (format "A value specified by an expression that is calculated only at the last moment possible."
- \n "Afterwards, the value is cached for future reference."))
-
-(documentation: /.lazy
- "Specifies a lazy value by providing the expression that computes it."
- [(lazy eager_computation)])
-
(.def .public documentation
(.List $.Module)
($.module /._
""
- [..Lazy
- ..lazy
- ($.default /.value)
+ [($.default /.value)
($.default /.equivalence)
($.default /.functor)
($.default /.apply)
- ($.default /.monad)]
+ ($.default /.monad)
+
+ ($.documentation (/.Lazy it)
+ (format "A value specified by an expression that is calculated only at the last moment possible."
+ \n "Afterwards, the value is cached for future reference."))
+
+ ($.documentation /.lazy
+ "Specifies a lazy value by providing the expression that computes it."
+ [(lazy eager_computation)])]
[]))
diff --git a/stdlib/source/documentation/lux/control/maybe.lux b/stdlib/source/documentation/lux/control/maybe.lux
index 7b6176f48..0c0ff167e 100644
--- a/stdlib/source/documentation/lux/control/maybe.lux
+++ b/stdlib/source/documentation/lux/control/maybe.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except if loop)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,48 +10,44 @@
[\\library
["[0]" /]])
-(documentation: /.lifted
- "Wraps a monadic value with Maybe machinery."
- [(lifted monad)])
-
-(documentation: /.else
- (format "Allows you to provide a default value that will be used"
- \n "if a (Maybe x) value turns out to be .#None."
- \n "Note: the expression for the default value will not be computed if the base computation succeeds.")
- [(else +20 {.#Some +10})
- "=>"
- +10]
- [(else +20 {.#None})
- "=>"
- +20])
-
-(documentation: /.trusted
- (format "Assumes that a Maybe value is a .#Some and yields its value."
- \n "Raises/throws a runtime error otherwise."
- \n "WARNING: Use with caution.")
- [(trusted trusted_computation)])
-
-(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 /._
""
- [..lifted
- ..else
- ..trusted
- ..when
- ($.default /.monoid)
+ [($.default /.monoid)
($.default /.functor)
($.default /.apply)
($.default /.monad)
($.default /.equivalence)
($.default /.hash)
($.default /.with)
- ($.default /.list)]
+ ($.default /.list)
+
+ ($.documentation /.lifted
+ "Wraps a monadic value with Maybe machinery."
+ [(lifted monad)])
+
+ ($.documentation /.else
+ (format "Allows you to provide a default value that will be used"
+ \n "if a (Maybe x) value turns out to be .#None."
+ \n "Note: the expression for the default value will not be computed if the base computation succeeds.")
+ [(else +20 {.#Some +10})
+ "=>"
+ +10]
+ [(else +20 {.#None})
+ "=>"
+ +20])
+
+ ($.documentation /.trusted
+ (format "Assumes that a Maybe value is a .#Some and yields its value."
+ \n "Raises/throws a runtime error otherwise."
+ \n "WARNING: Use with caution.")
+ [(trusted trusted_computation)])
+
+ ($.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))])]
[]))
diff --git a/stdlib/source/documentation/lux/control/parser.lux b/stdlib/source/documentation/lux/control/parser.lux
index b20bb433f..426854632 100644
--- a/stdlib/source/documentation/lux/control/parser.lux
+++ b/stdlib/source/documentation/lux/control/parser.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except or and not)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -22,149 +22,122 @@
["[1][0]" type]
["[1][0]" xml]])
-(documentation: (/.Parser state it)
- "A generic parser.")
-
-(documentation: /.assertion
- "Fails with the given message if the test is #0."
- [(assertion message test)])
+(.def .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [($.default /.functor)
+ ($.default /.apply)
+ ($.default /.monad)
-(documentation: /.maybe
- "Optionality combinator."
- [(maybe parser)])
+ ($.documentation (/.Parser state it)
+ "A generic 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 /.assertion
+ "Fails with the given message if the test is #0."
+ [(assertion message test)])
-(documentation: /.and
- "Sequencing combinator."
- [(and first second)])
+ ($.documentation /.maybe
+ "Optionality combinator."
+ [(maybe parser)])
-(documentation: /.or
- "Heterogeneous alternative combinator."
- [(or left right)])
+ ($.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: /.either
- "Homogeneous alternative combinator."
- [(either this that)])
+ ($.documentation /.and
+ "Sequencing combinator."
+ [(and first second)])
-(documentation: /.some
- "0-or-more combinator."
- [(some parser)])
+ ($.documentation /.or
+ "Heterogeneous alternative combinator."
+ [(or left right)])
-(documentation: /.many
- "1-or-more combinator."
- [(many parser)])
+ ($.documentation /.either
+ "Homogeneous alternative combinator."
+ [(either this that)])
-(documentation: /.exactly
- "Parse exactly N times."
- [(exactly amount parser)])
+ ($.documentation /.some
+ "0-or-more combinator."
+ [(some parser)])
-(documentation: /.at_least
- "Parse at least N times."
- [(at_least amount parser)])
+ ($.documentation /.many
+ "1-or-more combinator."
+ [(many parser)])
-(documentation: /.at_most
- "Parse at most N times."
- [(at_most amount parser)])
+ ($.documentation /.exactly
+ "Parse exactly N times."
+ [(exactly amount parser)])
-(documentation: /.between
- ""
- [(between minimum additional parser)])
+ ($.documentation /.at_least
+ "Parse at least N times."
+ [(at_least amount parser)])
-(documentation: /.separated_by
- "Parses instances of 'parser' that are separated by instances of 'separator'."
- [(separated_by separator parser)])
+ ($.documentation /.at_most
+ "Parse at most N times."
+ [(at_most amount parser)])
-(documentation: /.not
- "Only succeeds when the underlying parser fails."
- [(not parser)])
+ ($.documentation /.between
+ ""
+ [(between minimum additional parser)])
-(documentation: /.failure
- "Always fail with this 'message'."
- [(failure message)])
+ ($.documentation /.separated_by
+ "Parses instances of 'parser' that are separated by instances of 'separator'."
+ [(separated_by separator parser)])
-(documentation: /.lifted
- "Lift a potentially failed computation into a parser."
- [(lifted operation)])
+ ($.documentation /.not
+ "Only succeeds when the underlying parser fails."
+ [(not parser)])
-(documentation: /.else
- "If the given parser fails, returns the default value."
- [(else value parser)])
+ ($.documentation /.failure
+ "Always fail with this 'message'."
+ [(failure message)])
-(documentation: /.remaining
- "Yield the remaining input (without consuming it).")
+ ($.documentation /.lifted
+ "Lift a potentially failed computation into a parser."
+ [(lifted operation)])
-(documentation: /.rec
- "Combinator for recursive parsers."
- [(rec parser)])
+ ($.documentation /.else
+ "If the given parser fails, returns the default value."
+ [(else value parser)])
-(documentation: /.after
- "Run the parser after another one (whose output is ignored)."
- [(after param subject)])
+ ($.documentation /.remaining
+ "Yield the remaining input (without consuming it).")
-(documentation: /.before
- "Run the parser before another one (whose output is ignored)."
- [(before param subject)])
+ ($.documentation /.rec
+ "Combinator for recursive parsers."
+ [(rec parser)])
-(documentation: /.only
- "Only succeed when the parser's output passes a test."
- [(only test parser)])
+ ($.documentation /.after
+ "Run the parser after another one (whose output is ignored)."
+ [(after param subject)])
-(documentation: /.parses?
- "Ignore a parser's output and just verify that it succeeds."
- [(parses? parser)])
+ ($.documentation /.before
+ "Run the parser before another one (whose output is ignored)."
+ [(before param subject)])
-(documentation: /.parses
- "Ignore a parser's output and just execute it."
- [(parses parser)])
+ ($.documentation /.only
+ "Only succeed when the parser's output passes a test."
+ [(only test 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 /.parses?
+ "Ignore a parser's output and just verify that it succeeds."
+ [(parses? parser)])
-(documentation: /.codec
- "Decode the output of a parser using a codec."
- [(codec codec parser)])
+ ($.documentation /.parses
+ "Ignore a parser's output and just execute it."
+ [(parses 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)]
+ ($.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)])]
[/analysis.documentation
/binary.documentation
/cli.documentation
diff --git a/stdlib/source/documentation/lux/control/pipe.lux b/stdlib/source/documentation/lux/control/pipe.lux
index e3fd4900a..614e8f5c4 100644
--- a/stdlib/source/documentation/lux/control/pipe.lux
+++ b/stdlib/source/documentation/lux/control/pipe.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except let cond if exec case)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,109 +10,98 @@
[\\library
["[0]" /]])
-(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))))])
+(.def .public documentation
+ (.List $.Module)
+ ($.module /._
+ "Composable extensions to the piping macros (|> and <|) that enhance them with various abilities."
+ [($.documentation /.new
+ "Ignores the piped argument, and begins a new pipe."
+ [(n.= 1
+ (|> 20
+ (n.* 3)
+ (n.+ 4)
+ (new 0 [++])))])
-(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 /.let
+ "Gives a name to the piped-argument, within the given expression."
+ [(n.= 10
+ (|> 5
+ (let x (n.+ x x))))])
-(documentation: /.if
- "If-branching."
- [(same? (if (n.even? sample)
- "even"
- "odd")
- (|> sample
- (if [n.even?]
- [(new "even" [])]
- [(new "odd" [])])))])
+ ($.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: /.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 /.if
+ "If-branching."
+ [(same? (if (n.even? sample)
+ "even"
+ "odd")
+ (|> sample
+ (if [n.even?]
+ [(new "even" [])]
+ [(new "odd" [])])))])
-(documentation: /.while
- (format "While loops for pipes."
- \n "Both the testing and calculating steps are pipes and must be given inside tuples.")
- [(|> +1
- (while [(i.< +10)]
- [++]))])
+ ($.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: /.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 /.while
+ (format "While loops for pipes."
+ \n "Both the testing and calculating steps are pipes and must be given inside tuples.")
+ [(|> +1
+ (while [(i.< +10)]
+ [++]))])
-(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 /.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: /.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#encoded]))
- "=>"
- [+50 +2 "+5"]])
+ ($.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: /.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"
- _ "???"))])
+ ($.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#encoded]))
+ "=>"
+ [+50 +2 "+5"]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- "Composable extensions to the piping macros (|> and <|) that enhance them with various abilities."
- [..new
- ..let
- ..cond
- ..if
- ..when
- ..while
- ..do
- ..exec
- ..tuple
- ..case]
+ ($.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"
+ _ "???"))])]
[]))
diff --git a/stdlib/source/documentation/lux/control/reader.lux b/stdlib/source/documentation/lux/control/reader.lux
index 6dec9ff36..c411c6f32 100644
--- a/stdlib/source/documentation/lux/control/reader.lux
+++ b/stdlib/source/documentation/lux/control/reader.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except local)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,38 +10,32 @@
[\\library
["[0]" /]])
-(documentation: (/.Reader environment it)
- "Computations that have access to some environmental value.")
+(.def .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [($.default /.functor)
+ ($.default /.apply)
+ ($.default /.monad)
-(documentation: /.read
- "Get the environment.")
+ ($.documentation (/.Reader environment it)
+ "Computations that have access to some environmental value.")
-(documentation: /.local
- "Run computation with a locally-modified environment."
- [(local change proc)])
+ ($.documentation /.read
+ "Get the environment.")
-(documentation: /.result
- "Executes the reader against the given environment."
- [(result env proc)])
+ ($.documentation /.local
+ "Run computation with a locally-modified environment."
+ [(local change proc)])
-(documentation: /.with
- "Monad transformer for Reader."
- [(with monad)])
+ ($.documentation /.result
+ "Executes the reader against the given environment."
+ [(result env proc)])
-(documentation: /.lifted
- "Lift monadic values to the Reader wrapper.")
+ ($.documentation /.with
+ "Monad transformer for Reader."
+ [(with monad)])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [..Reader
- ..read
- ..local
- ..result
- ..with
- ..lifted
- ($.default /.functor)
- ($.default /.apply)
- ($.default /.monad)]
+ ($.documentation /.lifted
+ "Lift monadic values to the Reader wrapper.")]
[]))
diff --git a/stdlib/source/documentation/lux/control/region.lux b/stdlib/source/documentation/lux/control/region.lux
index dcfed365c..c0da27237 100644
--- a/stdlib/source/documentation/lux/control/region.lux
+++ b/stdlib/source/documentation/lux/control/region.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except if loop)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,42 +10,36 @@
[\\library
["[0]" /]])
-(documentation: (/.Region r ! it)
- (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 /.clean_up_error)
($.default /.functor)
($.default /.apply)
- ($.default /.monad)]
+ ($.default /.monad)
+
+ ($.documentation (/.Region r ! it)
+ (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)])]
[]))
diff --git a/stdlib/source/documentation/lux/control/remember.lux b/stdlib/source/documentation/lux/control/remember.lux
index cdc476e46..3d40127a4 100644
--- a/stdlib/source/documentation/lux/control/remember.lux
+++ b/stdlib/source/documentation/lux/control/remember.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,39 +10,36 @@
[\\library
["[0]" /]])
-(documentation: /.remember
- (format "A message with an expiration date."
- \n "Can have an optional piece of code to focus on.")
- [(remember "2022-04-01"
- "Do this, that and the other.")]
- [(remember "2022-04-01"
- "Improve the performace."
- (some (complicated (computation 123))))])
-
-(documentation: /.to_do
- (format "A TODO message with an expiration date."
- \n "Can have an optional piece of code to focus on.")
- [(to_do "2022-04-01"
- "Do this, that and the other.")]
- [(to_do "2022-04-01"
- "Improve the performace."
- (some (complicated (computation 123))))])
-
-(documentation: /.fix_me
- (format "A FIXME message with an expiration date."
- \n "Can have an optional piece of code to focus on.")
- [(fix_me "2022-04-01"
- "Do this, that and the other.")]
- [(fix_me "2022-04-01"
- "Improve the performace."
- (some (complicated (computation 123))))])
-
(.def .public documentation
(.List $.Module)
($.module /._
""
- [..remember
- ..to_do
- ..fix_me
- ($.default /.must_remember)]
+ [($.default /.must_remember)
+
+ ($.documentation /.remember
+ (format "A message with an expiration date."
+ \n "Can have an optional piece of code to focus on.")
+ [(remember "2022-04-01"
+ "Do this, that and the other.")]
+ [(remember "2022-04-01"
+ "Improve the performace."
+ (some (complicated (computation 123))))])
+
+ ($.documentation /.to_do
+ (format "A TODO message with an expiration date."
+ \n "Can have an optional piece of code to focus on.")
+ [(to_do "2022-04-01"
+ "Do this, that and the other.")]
+ [(to_do "2022-04-01"
+ "Improve the performace."
+ (some (complicated (computation 123))))])
+
+ ($.documentation /.fix_me
+ (format "A FIXME message with an expiration date."
+ \n "Can have an optional piece of code to focus on.")
+ [(fix_me "2022-04-01"
+ "Do this, that and the other.")]
+ [(fix_me "2022-04-01"
+ "Improve the performace."
+ (some (complicated (computation 123))))])]
[]))
diff --git a/stdlib/source/documentation/lux/control/security.lux b/stdlib/source/documentation/lux/control/security.lux
index 006fbfd0b..2c18b0150 100644
--- a/stdlib/source/documentation/lux/control/security.lux
+++ b/stdlib/source/documentation/lux/control/security.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]
diff --git a/stdlib/source/documentation/lux/control/state.lux b/stdlib/source/documentation/lux/control/state.lux
index a381f42f0..fa5a0ee5f 100644
--- a/stdlib/source/documentation/lux/control/state.lux
+++ b/stdlib/source/documentation/lux/control/state.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except local)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,73 +10,60 @@
[\\library
["[0]" /]])
-(documentation: (/.State state it)
- "Stateful computations.")
+(.def .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [($.default /.functor)
+ ($.default /.apply)
+ ($.default /.monad)
-(documentation: /.get
- "Read the current state.")
+ ($.documentation (/.State state it)
+ "Stateful computations.")
-(documentation: /.put
- "Set the new state."
- [(put new_state)])
+ ($.documentation /.get
+ "Read the current state.")
-(documentation: /.update
- "Compute the new state."
- [(update change)])
+ ($.documentation /.put
+ "Set the new state."
+ [(put new_state)])
-(documentation: /.use
- "Run a function on the current state."
- [(use user)])
+ ($.documentation /.update
+ "Compute the new state."
+ [(update change)])
-(documentation: /.local
- "Run the computation with a locally-modified state."
- [(local change action)])
+ ($.documentation /.use
+ "Run a function on the current state."
+ [(use user)])
-(documentation: /.result
- "Run a stateful computation."
- [(result state action)])
+ ($.documentation /.local
+ "Run the computation with a locally-modified state."
+ [(local change action)])
-(documentation: /.while
- "A stateful while loop."
- [(while condition body)])
+ ($.documentation /.result
+ "Run a stateful computation."
+ [(result state action)])
-(documentation: /.do_while
- "A stateful do-while loop."
- [(do_while condition body)])
+ ($.documentation /.while
+ "A stateful while loop."
+ [(while condition body)])
-(documentation: /.+State
- "Stateful computations decorated by a monad.")
+ ($.documentation /.do_while
+ "A stateful do-while loop."
+ [(do_while condition body)])
-(documentation: /.result'
- "Execute a stateful computation decorated by a monad."
- [(result' state action)])
+ ($.documentation /.+State
+ "Stateful computations decorated by a monad.")
-(documentation: /.with
- "A monad transformer to create composite stateful computations."
- [(with monad)])
+ ($.documentation /.result'
+ "Execute a stateful computation decorated by a monad."
+ [(result' state action)])
-(documentation: /.lifted
- "Lift monadic values to the +State wrapper."
- [(lifted monad ma)])
+ ($.documentation /.with
+ "A monad transformer to create composite stateful computations."
+ [(with monad)])
-(.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)]
+ ($.documentation /.lifted
+ "Lift monadic values to the +State wrapper."
+ [(lifted monad ma)])]
[]))
diff --git a/stdlib/source/documentation/lux/control/thread.lux b/stdlib/source/documentation/lux/control/thread.lux
index cbfdab03b..587c165a8 100644
--- a/stdlib/source/documentation/lux/control/thread.lux
+++ b/stdlib/source/documentation/lux/control/thread.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except local)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,48 +10,40 @@
[\\library
["[0]" /]])
-(documentation: (/.Thread ! it)
- "An imperative process with access to mutable values.")
+(.def .public documentation
+ (.List $.Module)
+ ($.module /._
+ ""
+ [($.default /.functor)
+ ($.default /.apply)
+ ($.default /.monad)
-(documentation: (/.Box ! it)
- "A mutable box holding a value.")
+ ($.documentation (/.Thread ! it)
+ "An imperative process with access to mutable values.")
-(documentation: /.box
- "A brand-new box initialized to the given value."
- [(box init)])
+ ($.documentation (/.Box ! it)
+ "A mutable box holding a value.")
-(documentation: /.read!
- "Reads the current value in the box."
- [(read! box)])
+ ($.documentation /.box
+ "A brand-new box initialized to the given value."
+ [(box init)])
-(documentation: /.write!
- "Mutates the value in the box."
- [(write! value box)])
+ ($.documentation /.read!
+ "Reads the current value in the box."
+ [(read! box)])
-(documentation: /.result
- "Executes the imperative thread in a self-contained way."
- [(result thread)])
+ ($.documentation /.write!
+ "Mutates the value in the box."
+ [(write! value box)])
-(documentation: /.io
- "Transforms the imperative thread into an I/O computation.")
+ ($.documentation /.result
+ "Executes the imperative thread in a self-contained way."
+ [(result thread)])
-(documentation: /.update!
- "Update a box's value by applying a function to it."
- [(update! f box)])
+ ($.documentation /.io
+ "Transforms the imperative thread into an I/O computation.")
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [..Thread
- ..Box
- ..box
- ..read!
- ..write!
- ..result
- ..io
- ..update!
- ($.default /.functor)
- ($.default /.apply)
- ($.default /.monad)]
+ ($.documentation /.update!
+ "Update a box's value by applying a function to it."
+ [(update! f box)])]
[]))
diff --git a/stdlib/source/documentation/lux/control/try.lux b/stdlib/source/documentation/lux/control/try.lux
index 31894e7d0..0283736a3 100644
--- a/stdlib/source/documentation/lux/control/try.lux
+++ b/stdlib/source/documentation/lux/control/try.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except local)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,53 +10,46 @@
[\\library
["[0]" /]])
-(documentation: (/.Try it)
- "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 /.functor)
($.default /.apply)
($.default /.monad)
- ($.default /.equivalence)]
+ ($.default /.equivalence)
+
+ ($.documentation (/.Try it)
+ "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!"}))])]
[]))
diff --git a/stdlib/source/documentation/lux/control/writer.lux b/stdlib/source/documentation/lux/control/writer.lux
index e22842527..b824174ec 100644
--- a/stdlib/source/documentation/lux/control/writer.lux
+++ b/stdlib/source/documentation/lux/control/writer.lux
@@ -1,7 +1,7 @@
(.require
[library
[lux (.except local)
- ["$" documentation (.only documentation:)]
+ ["$" documentation]
[data
[text (.only \n)
["%" \\format (.only format)]]]
@@ -10,30 +10,26 @@
[\\library
["[0]" /]])
-(documentation: (/.Writer log value)
- "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 /.functor)
($.default /.apply)
- ($.default /.monad)]
+ ($.default /.monad)
+
+ ($.documentation (/.Writer log value)
+ "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)])]
[]))
diff --git a/stdlib/source/documentation/lux/data/format/binary.lux b/stdlib/source/documentation/lux/data/format/binary.lux
index 64ece5b0b..b2ea53f63 100644
--- a/stdlib/source/documentation/lux/data/format/binary.lux
+++ b/stdlib/source/documentation/lux/data/format/binary.lux
@@ -22,12 +22,12 @@
(documentation: /.instance
"Given a specification of how to construct binary data, yields a binary blob that matches it.")
-(documentation: (/.Writer it)
+(documentation: (/.Format it)
"An operation that knows how to write information into a binary blob.")
(documentation: /.result
"Yields a binary blob with all the information written to it."
- [(result writer value)])
+ [(result format value)])
(documentation: /.or
""
@@ -38,7 +38,7 @@
[(and pre post)])
(documentation: /.rec
- "A combinator for recursive writers."
+ "A combinator for recursive formats."
[(rec body)])
(documentation: /.segment
@@ -53,7 +53,7 @@
..Specification
..no_op
..instance
- ..Writer
+ ..Format
..result
..or
..and
diff --git a/stdlib/source/documentation/lux/data/format/tar.lux b/stdlib/source/documentation/lux/data/format/tar.lux
index 5f58a2215..8da6c890f 100644
--- a/stdlib/source/documentation/lux/data/format/tar.lux
+++ b/stdlib/source/documentation/lux/data/format/tar.lux
@@ -81,7 +81,7 @@
($.default /.Contiguous)
($.default /.Entry)
($.default /.Tar)
- ($.default /.writer)
+ ($.default /.format)
($.default /.wrong_checksum)
($.default /.invalid_end_of_archive)
($.default /.parser)]