aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/documentation
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/documentation')
-rw-r--r--stdlib/source/documentation/lux.lux1703
-rw-r--r--stdlib/source/documentation/lux/program.lux103
-rw-r--r--stdlib/source/documentation/lux/test.lux118
-rw-r--r--stdlib/source/documentation/lux/test/coverage.lux20
-rw-r--r--stdlib/source/documentation/lux/test/property.lux86
-rw-r--r--stdlib/source/documentation/lux/test/tally.lux26
-rw-r--r--stdlib/source/documentation/lux/test/unit.lux51
-rw-r--r--stdlib/source/documentation/lux/world.lux4
-rw-r--r--stdlib/source/documentation/lux/world/console.lux43
-rw-r--r--stdlib/source/documentation/lux/world/environment.lux102
-rw-r--r--stdlib/source/documentation/lux/world/file.lux105
-rw-r--r--stdlib/source/documentation/lux/world/file/watch.lux67
-rw-r--r--stdlib/source/documentation/lux/world/input/keyboard.lux187
-rw-r--r--stdlib/source/documentation/lux/world/locale.lux37
-rw-r--r--stdlib/source/documentation/lux/world/locale/language.lux1192
-rw-r--r--stdlib/source/documentation/lux/world/locale/territory.lux591
-rw-r--r--stdlib/source/documentation/lux/world/net.lux37
-rw-r--r--stdlib/source/documentation/lux/world/net/http/client.lux51
-rw-r--r--stdlib/source/documentation/lux/world/net/http/status.lux159
-rw-r--r--stdlib/source/documentation/lux/world/net/uri.lux19
-rw-r--r--stdlib/source/documentation/lux/world/output/video/resolution.lux69
-rw-r--r--stdlib/source/documentation/lux/world/shell.lux67
-rw-r--r--stdlib/source/documentation/lux/world/time.lux101
-rw-r--r--stdlib/source/documentation/lux/world/time/date.lux53
-rw-r--r--stdlib/source/documentation/lux/world/time/day.lux39
-rw-r--r--stdlib/source/documentation/lux/world/time/duration.lux73
-rw-r--r--stdlib/source/documentation/lux/world/time/instant.lux95
-rw-r--r--stdlib/source/documentation/lux/world/time/month.lux51
-rw-r--r--stdlib/source/documentation/lux/world/time/year.lux79
29 files changed, 2746 insertions, 2582 deletions
diff --git a/stdlib/source/documentation/lux.lux b/stdlib/source/documentation/lux.lux
index 28350a7c9..68491c807 100644
--- a/stdlib/source/documentation/lux.lux
+++ b/stdlib/source/documentation/lux.lux
@@ -10,10 +10,10 @@
["[0]" text (.only \n)
["%" \\format (.only format)]]
[collection
- ["[0]" list]
+ ["[0]" list (.use "[1]#[0]" monoid)]
["[0]" set]]]]]
[\\library
- ["[0]" /]]
+ ["[0]" / (.except)]]
["[0]" /
["[1][0]" abstract]
["[1][0]" control]
@@ -27,872 +27,877 @@
["[1][0]" test]
["[1][0]" world]])
-(.`` (.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.prelude
- (format "The name of the prelude module"
- \n "Value: " (%.text /.prelude)))
+(`` (def .public documentation
+ (List $.Documentation)
+ (list.partial ($.module /._
+ "")
- ($.definition /.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."))
+ ($.definition /.prelude
+ (format "The name of the prelude module"
+ \n "Value: " (%.text /.prelude)))
- ($.definition /.Nothing
- (format "The type of things whose type is undefined."
- \n "Useful for expressions that cause errors or other 'extraordinary' conditions."))
+ ($.definition /.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."))
- ($.definition (/.List item)
- "A potentially empty list of values.")
+ ($.definition /.Nothing
+ (format "The type of things whose type is undefined."
+ \n "Useful for expressions that cause errors or other 'extraordinary' conditions."))
- ($.definition /.Bit
- "Your standard, run-of-the-mill boolean values (as #0 or #1 bits).")
+ ($.definition (/.List item)
+ "A potentially empty list of values.")
- ($.definition (/.I64 kind)
- "64-bit integers without any semantics.")
+ ($.definition /.Bit
+ "Your standard, run-of-the-mill boolean values (as #0 or #1 bits).")
- ($.definition /.Nat
- (format "Natural numbers (unsigned integers)."
- \n "They start at zero (0) and extend in the positive direction."))
+ ($.definition (/.I64 kind)
+ "64-bit integers without any semantics.")
- ($.definition /.Int
- "Your standard, run-of-the-mill integer numbers.")
+ ($.definition /.Nat
+ (format "Natural numbers (unsigned integers)."
+ \n "They start at zero (0) and extend in the positive direction."))
- ($.definition /.Rev
- (format "Fractional numbers that live in the interval [0,1)."
- \n "Useful for probability, and other domains that work within that interval."))
+ ($.definition /.Int
+ "Your standard, run-of-the-mill integer numbers.")
- ($.definition /.Frac
- "Your standard, run-of-the-mill floating-point (fractional) numbers.")
+ ($.definition /.Rev
+ (format "Fractional numbers that live in the interval [0,1)."
+ \n "Useful for probability, and other domains that work within that interval."))
- ($.definition /.Text
- "Your standard, run-of-the-mill string values.")
+ ($.definition /.Frac
+ "Your standard, run-of-the-mill floating-point (fractional) numbers.")
- ($.definition /.Symbol
- (format "A name for a Lux definition."
- \n "It includes the module of provenance."))
+ ($.definition /.Text
+ "Your standard, run-of-the-mill string values.")
- ($.definition (/.Maybe value)
- "A potentially missing value.")
+ ($.definition /.Symbol
+ (format "A name for a Lux definition."
+ \n "It includes the module of provenance."))
- ($.definition /.Type
- "This type represents the data-structures that are used to specify types themselves.")
+ ($.definition (/.Maybe value)
+ "A potentially missing value.")
- ($.definition /.Location
- "Locations are for specifying the location of Code nodes in Lux files during compilation.")
-
- ($.definition (/.Ann meta_data datum)
- "The type of things that can be annotated with meta-data of arbitrary types.")
-
- ($.definition /.Code
- "The type of Code nodes for Lux syntax.")
-
- ($.definition /.private
- "The export policy for private/local definitions.")
-
- ($.definition /.local
- "The export policy for private/local definitions.")
-
- ($.definition /.public
- "The export policy for public/global definitions.")
-
- ($.definition /.global
- "The export policy for public/global definitions.")
-
- ($.definition /.Definition
- "Represents all the data associated with a definition: its type, its annotations, and its value.")
-
- ($.definition /.Global
- "Represents all the data associated with a global constant.")
-
- ($.definition (/.Either left right)
- "A choice between two values of different types.")
-
- ($.definition /.Module
- "All the information contained within a Lux module.")
-
- ($.definition /.Mode
- "A sign that shows the conditions under which the compiler is running.")
-
- ($.definition /.Info
- "Information about the current version and type of compiler that is running.")
-
- ($.definition /.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."))
-
- ($.definition (/.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."))
-
- ($.definition /.Macro
- "Functions that run at compile-time and allow you to transform and extend the language in powerful ways.")
-
- ($.definition /.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))))])
-
- ($.definition /.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)]))])
-
- ($.definition /.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))])])
-
- ($.definition /.->
- "Function types."
- ["This is the type of a function that takes 2 Ints and returns an Int."
- (-> Int Int Int)])
-
- ($.definition /.list
- "List literals."
- [(is (List Nat)
- (list 0 1 2 3))])
-
- ($.definition /.Union
- "Union types."
- [(Union Bit Nat Text)]
- [(= Nothing
- (Union))])
-
- ($.definition /.Tuple
- "Tuple types."
- [(Tuple Bit Nat Text)]
- [(= Any
- (Tuple))])
-
- ($.definition /.Or
- "An alias for the Union type constructor."
- [(= (Union Bit Nat Text)
- (Or Bit Nat Text))]
- [(= (Union)
- (Or))])
-
- ($.definition /.And
- "An alias for the Tuple type constructor."
- [(= (Tuple Bit Nat Text)
- (And Bit Nat Text))]
- [(= (Tuple)
- (And))])
-
- ($.definition /.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?")])
-
- ($.definition /.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?"))])
-
- ($.definition /.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!"])
-
- ($.definition /.Primitive
- "Macro to treat define new primitive types."
- [(Primitive "java.lang.Object")]
- [(Primitive "java.util.List" [(Primitive "java.lang.Long")])])
-
- ($.definition /.`
- (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))))])
-
- ($.definition /.`'
- (format "Unhygienic quasi-quotation as a macro."
- \n "Unquote (,) and unquote-splice (,*) must also be used as forms.")
- [(`' (def (, name)
- (function (_ (,* args))
- (, body))))])
-
- ($.definition /.'
- "Quotation as a macro."
- [(' YOLO)])
-
- ($.definition /.|>
- "Piping macro."
- [(|> elems
- (list#each int#encoded)
- (interposed " ")
- (mix text#composite ""))
- "=>"
- (mix text#composite ""
- (interposed " "
- (list#each int#encoded
- elems)))])
-
- ($.definition /.<|
- "Reverse piping macro."
- [(<| (mix text#composite "")
- (interposed " ")
- (list#each int#encoded)
- elems)
- "=>"
- (mix text#composite ""
- (interposed " "
- (list#each int#encoded
- elems)))])
-
- ($.definition /.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]
- )])
-
- ($.definition /.not
- "Bit negation."
- [(not #1)
- "=>"
- #0]
- [(not #0)
- "=>"
- #1])
-
- ($.definition /.type
- "Takes a type expression and returns its representation as data-structure."
- [(type_literal (All (_ a)
- (Maybe (List a))))])
-
- ($.definition /.is
- "The type-annotation macro."
- [(is (List Int)
- (list +1 +2 +3))])
-
- ($.definition /.as
- "The type-coercion macro."
- [(as Dinosaur
- (list +1 +2 +3))])
-
- ($.definition /.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 @})))])
-
- ($.definition /.exec
- "Sequential execution of expressions (great for side-effects)."
- [(exec
- (log! "#1")
- (log! "#2")
- (log! "#3")
- "YOLO")])
-
- ($.definition /.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})])
-
- ($.definition /.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))
- (list x y z)
- {#Some (all * x y z)}
-
- _
- {#None})])
-
- ... ($.definition /.^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})
- ... true
-
- ... _
- ... false))])
-
- ($.definition /.let
- (format "Creates local bindings."
- \n "Can (optionally) use pattern-matching macros when binding.")
- [(let [x (foo bar)
- y (baz quux)]
- (op x y))])
-
- ($.definition /.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))))))])
-
- ($.definition /.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))])
-
- ($.definition /.macro
- "Macro-definition macro."
- [(def .public symbol
- (macro (_ tokens)
- (case tokens
- (^with_template [<tag>]
- [(list [_ {<tag> [module name]}])
- (in (list (` [(, (text$ module)) (, (text$ name))])))])
- ([#Symbol])
-
- _
- (failure "Wrong syntax for symbol"))))])
-
- ($.definition /.and
- "Short-circuiting 'and'."
- [(and #1 #0)
- "=>"
- #0]
- [(and #1 #1)
- "=>"
- #1])
-
- ($.definition /.or
- "Short-circuiting 'or'."
- [(or #1 #0)
- "=>"
- #1]
- [(or #0 #0)
- "=>"
- #0])
-
- ($.definition /.panic!
- "Causes an error, with the given error message."
- [(panic! "OH NO!")])
-
- ($.definition /.implementation
- "Express a value that implements an interface."
- [(is (Order Int)
- (implementation
- (def equivalence
- equivalence)
- (def (< reference subject)
- (< reference subject))
- ))])
-
- ($.definition /.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}))])
-
- ($.definition /.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)]))])
-
- ($.definition /.type
- "The type-definition macro."
- [(type (List a)
- {#End}
- {#Item a (List a)})])
-
- ($.definition /.Interface
- "Interface definition."
- [(type .public (Order a)
- (Interface
- (is (Equivalence a)
- equivalence)
- (is (-> a a Bit)
- <)))])
-
- (.,, (.with_template [<name>]
- [($.definition <name>
- "Safe type-casting for I64 values.")]
-
- [/.i64]
- [/.nat]
- [/.int]
- [/.rev]
- ))
-
- ($.definition /.module_separator
- (format "Character used to separate the parts of module names."
- \n "Value: " (%.text /.module_separator)))
-
- ($.definition /.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}))))])
-
- ($.definition /.cond
- "Conditional branching with multiple test conditions."
- [(cond (even? num) "WHEN even"
- (odd? num) "WHEN odd"
- "ELSE")])
-
- ($.definition /.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))])
-
- ($.definition /.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 <))])
-
- ($.definition /.|>>
- "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>)
+ ($.definition /.Type
+ "This type represents the data-structures that are used to specify types themselves.")
+
+ ($.definition /.Location
+ "Locations are for specifying the location of Code nodes in Lux files during compilation.")
+
+ ($.definition (/.Ann meta_data datum)
+ "The type of things that can be annotated with meta-data of arbitrary types.")
+
+ ($.definition /.Code
+ "The type of Code nodes for Lux syntax.")
+
+ ($.definition /.private
+ "The export policy for private/local definitions.")
+
+ ($.definition /.local
+ "The export policy for private/local definitions.")
+
+ ($.definition /.public
+ "The export policy for public/global definitions.")
+
+ ($.definition /.global
+ "The export policy for public/global definitions.")
+
+ ($.definition /.Definition
+ "Represents all the data associated with a definition: its type, its annotations, and its value.")
+
+ ($.definition /.Global
+ "Represents all the data associated with a global constant.")
+
+ ($.definition (/.Either left right)
+ "A choice between two values of different types.")
+
+ ($.definition /.Module
+ "All the information contained within a Lux module.")
+
+ ($.definition /.Mode
+ "A sign that shows the conditions under which the compiler is running.")
+
+ ($.definition /.Info
+ "Information about the current version and type of compiler that is running.")
+
+ ($.definition /.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."))
+
+ ($.definition (/.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."))
+
+ ($.definition /.Macro
+ "Functions that run at compile-time and allow you to transform and extend the language in powerful ways.")
+
+ ($.definition /.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))))])
+
+ ($.definition /.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)]))])
+
+ ($.definition /.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))])])
+
+ ($.definition /.->
+ "Function types."
+ ["This is the type of a function that takes 2 Ints and returns an Int."
+ (-> Int Int Int)])
+
+ ($.definition /.list
+ "List literals."
+ [(is (List Nat)
+ (list 0 1 2 3))])
+
+ ($.definition /.Union
+ "Union types."
+ [(Union Bit Nat Text)]
+ [(= Nothing
+ (Union))])
+
+ ($.definition /.Tuple
+ "Tuple types."
+ [(Tuple Bit Nat Text)]
+ [(= Any
+ (Tuple))])
+
+ ($.definition /.Or
+ "An alias for the Union type constructor."
+ [(= (Union Bit Nat Text)
+ (Or Bit Nat Text))]
+ [(= (Union)
+ (Or))])
+
+ ($.definition /.And
+ "An alias for the Tuple type constructor."
+ [(= (Tuple Bit Nat Text)
+ (And Bit Nat Text))]
+ [(= (Tuple)
+ (And))])
+
+ ($.definition /.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?")])
+
+ ($.definition /.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?"))])
+
+ ($.definition /.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!"])
+
+ ($.definition /.Primitive
+ "Macro to treat define new primitive types."
+ [(Primitive "java.lang.Object")]
+ [(Primitive "java.util.List" [(Primitive "java.lang.Long")])])
+
+ ($.definition /.`
+ (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))))])
+
+ ($.definition /.`'
+ (format "Unhygienic quasi-quotation as a macro."
+ \n "Unquote (,) and unquote-splice (,*) must also be used as forms.")
+ [(`' (def (, name)
+ (function (_ (,* args))
+ (, body))))])
+
+ ($.definition /.'
+ "Quotation as a macro."
+ [(' YOLO)])
+
+ ($.definition /.|>
+ "Piping macro."
+ [(|> elems
+ (list#each int#encoded)
+ (interposed " ")
+ (mix text#composite ""))
+ "=>"
(mix text#composite ""
(interposed " "
- (list#each int#encoded <it>))))])
-
- ($.definition /.<<|
- "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>)
+ (list#each int#encoded
+ elems)))])
+
+ ($.definition /.<|
+ "Reverse piping macro."
+ [(<| (mix text#composite "")
+ (interposed " ")
+ (list#each int#encoded)
+ elems)
+ "=>"
(mix text#composite ""
(interposed " "
(list#each int#encoded
- <it>))))])
-
- ($.definition /.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)]])])
-
- ($.definition /.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)])
-
- ($.definition /.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))])
-
- ($.definition /.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))])
-
- ... ($.definition /.^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>]
- [($.definition <name>
- <doc>)]
-
- [/.++ "Increment function."]
- [/.-- "Decrement function."]
- ))
-
- ($.definition /.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
+ elems)))])
+
+ ($.definition /.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]
+ )])
+
+ ($.definition /.not
+ "Bit negation."
+ [(not #1)
+ "=>"
+ #0]
+ [(not #0)
+ "=>"
+ #1])
+
+ ($.definition /.type
+ "Takes a type expression and returns its representation as data-structure."
+ [(type_literal (All (_ a)
+ (Maybe (List a))))])
+
+ ($.definition /.is
+ "The type-annotation macro."
+ [(is (List Int)
+ (list +1 +2 +3))])
+
+ ($.definition /.as
+ "The type-coercion macro."
+ [(as Dinosaur
+ (list +1 +2 +3))])
+
+ ($.definition /.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 @})))])
+
+ ($.definition /.exec
+ "Sequential execution of expressions (great for side-effects)."
+ [(exec
+ (log! "#1")
+ (log! "#2")
+ (log! "#3")
+ "YOLO")])
+
+ ($.definition /.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})])
+
+ ($.definition /.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))
+ (list x y z)
+ {#Some (all * x y z)}
+
+ _
+ {#None})])
+
+ ... ($.definition /.^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})
+ ... true
+
+ ... _
+ ... false))])
+
+ ($.definition /.let
+ (format "Creates local bindings."
+ \n "Can (optionally) use pattern-matching macros when binding.")
+ [(let [x (foo bar)
+ y (baz quux)]
+ (op x y))])
+
+ ($.definition /.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))))))])
+
+ ($.definition /.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))])
+
+ ($.definition /.macro
+ "Macro-definition macro."
+ [(def .public symbol
+ (macro (_ tokens)
+ (case tokens
+ (^with_template [<tag>]
+ [(list [_ {<tag> [module name]}])
+ (in (list (` [(, (text$ module)) (, (text$ name))])))])
+ ([#Symbol])
+
+ _
+ (failure "Wrong syntax for symbol"))))])
+
+ ($.definition /.and
+ "Short-circuiting 'and'."
+ [(and #1 #0)
+ "=>"
+ #0]
+ [(and #1 #1)
+ "=>"
+ #1])
+
+ ($.definition /.or
+ "Short-circuiting 'or'."
+ [(or #1 #0)
+ "=>"
+ #1]
+ [(or #0 #0)
+ "=>"
+ #0])
+
+ ($.definition /.panic!
+ "Causes an error, with the given error message."
+ [(panic! "OH NO!")])
+
+ ($.definition /.implementation
+ "Express a value that implements an interface."
+ [(is (Order Int)
+ (implementation
+ (def equivalence
+ equivalence)
+ (def (< reference subject)
+ (< reference subject))
+ ))])
+
+ ($.definition /.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}))])
+
+ ($.definition /.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)]))])
+
+ ($.definition /.type
+ "The type-definition macro."
+ [(type (List a)
+ {#End}
+ {#Item a (List a)})])
+
+ ($.definition /.Interface
+ "Interface definition."
+ [(type .public (Order a)
+ (Interface
+ (is (Equivalence a)
+ equivalence)
+ (is (-> a a Bit)
+ <)))])
+
+ (,, (with_template [<name>]
+ [($.definition <name>
+ "Safe type-casting for I64 values.")]
+
+ [/.i64]
+ [/.nat]
+ [/.int]
+ [/.rev]
+ ))
+
+ ($.definition /.module_separator
+ (format "Character used to separate the parts of module names."
+ \n "Value: " (%.text /.module_separator)))
+
+ ($.definition /.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}))))])
+
+ ($.definition /.cond
+ "Conditional branching with multiple test conditions."
+ [(cond (even? num) "WHEN even"
+ (odd? num) "WHEN odd"
+ "ELSE")])
+
+ ($.definition /.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))])
+
+ ($.definition /.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 <))])
+
+ ($.definition /.|>>
+ "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>))))])
+
+ ($.definition /.<<|
+ "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>))))])
+
+ ($.definition /.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)]])])
+
+ ($.definition /.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)])
+
+ ($.definition /.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))])
+
+ ($.definition /.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))])
+
+ ... ($.definition /.^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>]
+ [($.definition <name>
+ <doc>)]
+
+ [/.++ "Increment function."]
+ [/.-- "Decrement function."]
+ ))
+
+ ($.definition /.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)
- (my_loop (++ count) (f x))
- x))])
-
- ($.definition /.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>
- )))])
-
- ($.definition /.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]
- (static [..my_nat ..my_text])
- true
-
- _
- false)
- (case [my_nat my_text]
- [(static ..my_nat) (static ..my_text)]
- true
-
- _
- false))])
-
- ... ($.definition /.^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) .true])
- ... (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)})])
-
- ($.definition /.symbol
- "Gives back a 2 tuple with the module and name parts, both as Text."
- [(symbol ..#doc)
- "=>"
- ["documentation/lux" "#doc"]])
-
- ($.definition /.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))])
-
- ($.definition /.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))])
-
- ... ($.definition /.^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)))])
-
- ... ($.definition /.^|>
- ... "Pipes the value being pattern-matched against prior to binding it to a variable."
- ... [(case input
- ... (^|> value [++ (% 10) (max 1)])
- ... (foo value))])
-
- ($.definition /.as_expected
- "Coerces the given expression to the type of whatever is expected."
- [(is Dinosaur
- (as_expected (is (List Nat)
- (list 1 2 3))))])
-
- ($.definition /.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))])
-
- ($.definition /.type_of
- "Generates the type corresponding to a given expression."
- [(let [my_num +123]
- (type_of my_num))
- "=="
- Int]
- [(type_of +123)
- "=="
- Int])
-
- ($.definition /.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)))])
-
- ($.definition /.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>))])
-
- ($.definition /.char
- "If given a 1-character text literal, yields the char-code of the sole character."
- [(is Nat
- (char "A"))
- "=>"
- 65])
-
- ($.definition /.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))])
-
- ($.definition /.``
- (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))))])
-
- ... ($.definition /.^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}))])
-
- ($.definition /.false
- "The boolean FALSE value.")
-
- ($.definition /.true
- "The boolean TRUE value.")
-
- ($.definition /.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))))])
-
- ($.definition (/.Code' w))
- ($.definition /.Alias)
- ($.definition (/.Bindings key value))
- ($.definition /.Ref)
- ($.definition /.Scope)
- ($.definition /.Source)
- ($.definition /.Module_State)
- ($.definition /.Type_Context)
- ($.definition /.Macro')
- ($.definition /.Label)
- ($.definition /.macro)]
- [/abstract.documentation
- /control.documentation
- /data.documentation
- /debug.documentation
- /documentation.documentation
- /ffi.documentation
- /math.documentation
- /meta.documentation
- /program.documentation
- /test.documentation
- /world.documentation])))
-
-(.def _
+ (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))])
+
+ ($.definition /.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>
+ )))])
+
+ ($.definition /.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]
+ (static [..my_nat ..my_text])
+ true
+
+ _
+ false)
+ (case [my_nat my_text]
+ [(static ..my_nat) (static ..my_text)]
+ true
+
+ _
+ false))])
+
+ ... ($.definition /.^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) .true])
+ ... (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)})])
+
+ ($.definition /.symbol
+ "Gives back a 2 tuple with the module and name parts, both as Text."
+ [(symbol ..#doc)
+ "=>"
+ ["documentation/lux" "#doc"]])
+
+ ($.definition /.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))])
+
+ ($.definition /.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))])
+
+ ... ($.definition /.^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)))])
+
+ ... ($.definition /.^|>
+ ... "Pipes the value being pattern-matched against prior to binding it to a variable."
+ ... [(case input
+ ... (^|> value [++ (% 10) (max 1)])
+ ... (foo value))])
+
+ ($.definition /.as_expected
+ "Coerces the given expression to the type of whatever is expected."
+ [(is Dinosaur
+ (as_expected (is (List Nat)
+ (list 1 2 3))))])
+
+ ($.definition /.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))])
+
+ ($.definition /.type_of
+ "Generates the type corresponding to a given expression."
+ [(let [my_num +123]
+ (type_of my_num))
+ "=="
+ Int]
+ [(type_of +123)
+ "=="
+ Int])
+
+ ($.definition /.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)))])
+
+ ($.definition /.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>))])
+
+ ($.definition /.char
+ "If given a 1-character text literal, yields the char-code of the sole character."
+ [(is Nat
+ (char "A"))
+ "=>"
+ 65])
+
+ ($.definition /.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))])
+
+ ($.definition /.``
+ (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))))])
+
+ ... ($.definition /.^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}))])
+
+ ($.definition /.false
+ "The boolean FALSE value.")
+
+ ($.definition /.true
+ "The boolean TRUE value.")
+
+ ($.definition /.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))))])
+
+ ($.definition (/.Code' w))
+ ($.definition /.Alias)
+ ($.definition (/.Bindings key value))
+ ($.definition /.Ref)
+ ($.definition /.Scope)
+ ($.definition /.Source)
+ ($.definition /.Module_State)
+ ($.definition /.Type_Context)
+ ($.definition /.Macro')
+ ($.definition /.Label)
+ ($.definition /.macro)
+
+ (all list#composite
+ /abstract.documentation
+ /control.documentation
+ /data.documentation
+ /debug.documentation
+ /documentation.documentation
+ /ffi.documentation
+ /math.documentation
+ /meta.documentation
+ /program.documentation
+ /test.documentation
+ /world.documentation
+ )
+ )))
+
+(def _
(program inputs
(io.io (debug.log! ($.markdown ..documentation)))))
diff --git a/stdlib/source/documentation/lux/program.lux b/stdlib/source/documentation/lux/program.lux
index bc126a34a..d0ea5d8ac 100644
--- a/stdlib/source/documentation/lux/program.lux
+++ b/stdlib/source/documentation/lux/program.lux
@@ -6,65 +6,70 @@
["[0]" io]]
[data
["[0]" text (.only \n)
- ["%" \\format (.only format)]]]]]
+ ["%" \\format (.only format)]]
+ [collection
+ ["[0]" list]]]]]
["[0]" \\parser]
[\\library
["[0]" /]])
-(.def \\parser
- (.List $.Module)
- ($.module \\parser._
- ""
- [($.definition (\\parser.Parser it)
- "A command-line interface parser.")
+(def \\parser
+ (List $.Documentation)
+ (list ($.module \\parser._
+ "")
+ ($.definition (\\parser.Parser it)
+ "A command-line interface parser.")
- ($.definition \\parser.result
- "Executes the parser and verifies that all inputs are processed."
- [(result parser inputs)])
+ ($.definition \\parser.result
+ "Executes the parser and verifies that all inputs are processed."
+ [(result parser inputs)])
- ($.definition \\parser.any
- "Just returns the next input without applying any logic.")
+ ($.definition \\parser.any
+ "Just returns the next input without applying any logic.")
- ($.definition \\parser.parse
- "Parses the next input with a parsing function."
- [(parse parser)])
+ ($.definition \\parser.parse
+ "Parses the next input with a parsing function."
+ [(parse parser)])
- ($.definition \\parser.this
- "Checks that a token is in the inputs."
- [(this reference)])
+ ($.definition \\parser.this
+ "Checks that a token is in the inputs."
+ [(this reference)])
- ($.definition \\parser.somewhere
- "Given a parser, tries to parse it somewhere in the inputs (i.e. not necessarily parsing the immediate inputs)."
- [(somewhere cli)])
+ ($.definition \\parser.somewhere
+ "Given a parser, tries to parse it somewhere in the inputs (i.e. not necessarily parsing the immediate inputs)."
+ [(somewhere cli)])
- ($.definition \\parser.end
- "Ensures there are no more inputs.")
+ ($.definition \\parser.end
+ "Ensures there are no more inputs.")
- ($.definition \\parser.named
- "Parses a named parameter and yields its value."
- [(named name value)])
+ ($.definition \\parser.named
+ "Parses a named parameter and yields its value."
+ [(named name value)])
- ($.definition \\parser.parameter
- "Parses a parameter that can have either a short or a long name."
- [(parameter [short long] value)])]
- []))
+ ($.definition \\parser.parameter
+ "Parses a parameter that can have either a short or a long name."
+ [(parameter [short long] value)])
+ ))
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.program
- "Defines the entry-point to a program (similar to the 'main' function/method in other programming languages)."
- ["Can take a list of all the input parameters to the program."
- (def _
- (program all_arguments
- (do io.monad
- [foo (initialize program)]
- (do_something_with all_arguments))))]
- ["Can also parse them using CLI parsers from the library/lux/control/parser/cli module."
- (def _
- (program [config configuration_parser]
- (do io.monad
- [data (initialize program with config)]
- (do_something_with data))))])]
- [..\\parser]))
+(def .public documentation
+ (List $.Documentation)
+ (list.partial ($.module /._
+ "")
+
+ ($.definition /.program
+ "Defines the entry-point to a program (similar to the 'main' function/method in other programming languages)."
+ ["Can take a list of all the input parameters to the program."
+ (def _
+ (program all_arguments
+ (do io.monad
+ [foo (initialize program)]
+ (do_something_with all_arguments))))]
+ ["Can also parse them using CLI parsers from the library/lux/control/parser/cli module."
+ (def _
+ (program [config configuration_parser]
+ (do io.monad
+ [data (initialize program with config)]
+ (do_something_with data))))])
+
+ ..\\parser
+ ))
diff --git a/stdlib/source/documentation/lux/test.lux b/stdlib/source/documentation/lux/test.lux
index 467b04150..7787512c5 100644
--- a/stdlib/source/documentation/lux/test.lux
+++ b/stdlib/source/documentation/lux/test.lux
@@ -1,104 +1,24 @@
(.require
[library
- [lux (.except and for)
+ [lux (.except)
["$" documentation]
[data
- ["[0]" text (.only \n)
- ["%" \\format (.only format)]]]]]
+ [collection
+ ["[0]" list (.use "[1]#[0]" monoid)]]]]]
[\\library
- ["[0]" /]])
-
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- "Tools for unit & property-based/generative testing."
- [($.definition /.must_try_test_at_least_once)
- ($.definition /.error_during_execution)
-
- ($.definition /.Tally
- "A record of successes and failures while executing tests.")
-
- ($.definition /.Assertion
- "An asynchronous operation that yields test results.")
-
- ($.definition /.Test
- "A test that relies on random data generation to thoroughly cover different scenarios.")
-
- ($.definition /.and'
- "Sequencing combinator (for assertions)."
- [(and' left right)])
-
- ($.definition /.and
- "Sequencing combinator."
- [(and left right)])
-
- ($.definition /.context
- "Adds a contextual description to a test's documentation."
- [(context description)])
-
- ($.definition /.failure
- "A failing test, with a given error message.")
-
- ($.definition /.assertion
- "Check that a condition is #1, and fail with the given message otherwise."
- [(assertion message condition)])
-
- ($.definition /.property
- "Check that a condition is #1, and fail with the given message otherwise."
- [(property message condition)])
-
- ($.definition /.lifted
- ""
- [(lifted message random)])
-
- ($.definition /.Seed
- "The seed value used for random testing (if that feature is used).")
-
- ($.definition /.seed
- (format "Execute the given test with a specific seed value."
- \n "This allows you to reproduce a failing test case as many times as you want while debugging.")
- [(seed value test)])
-
- ($.definition /.times
- (format "Allows executing a test several times."
- \n "By doing this, it's possible to thoroughly test code with many different scenarios."
- \n "This assumes that random data generation is being used in tests instead of fixed/constant inputs.")
- [(times amount test)])
-
- ($.definition /.run!
- (format "Executes a test, and exits the program with either a successful or a failing exit code."
- \n "WARNING: This procedure is only meant to be used in (program ...) forms.")
- [(run! test)])
-
- ($.definition /.coverage'
- (format "Specifies a test as covering one or more definitions."
- \n "Adds to the test tally information to track which definitions have been tested.")
- [(coverage' [definition/0 definition/1 ,,, definition/N]
- (is Bit
- (some "computation")))])
-
- ($.definition /.coverage
- (format "Specifies a test as covering one or more definitions."
- \n "Adds to the test tally information to track which definitions have been tested.")
- [(coverage [definition/0 definition/1 ,,, definition/N]
- (is Bit
- (some "computation")))])
-
- ($.definition /.for
- (format "Specifies a context for tests as covering one or more definitions."
- \n "Adds to the test tally information to track which definitions have been tested.")
- [(for [definition/0 definition/1 ,,, definition/N]
- (is Test
- some_test))])
-
- ($.definition /.covering
- (format "Specifies the module being covered by a test."
- \n "Adds tracking information to the tally to know which exported definitions in the module need to be covered.")
- [(covering .._
- (is Test
- some_test))])
-
- ($.definition /.in_parallel
- "Executes multiple tests in parallel (if the host platform supports it) to take advantage of multiple cores."
- [(in_parallel tests)])]
- []))
+ ["[0]" /
+ ["[1]" property]]]
+ ["[0]" /
+ ["[1][0]" coverage]
+ ["[1][0]" property]
+ ["[1][0]" tally]
+ ["[1][0]" unit]])
+
+(def .public documentation
+ (List $.Documentation)
+ (all list#composite
+ /coverage.documentation
+ /property.documentation
+ /tally.documentation
+ /unit.documentation
+ ))
diff --git a/stdlib/source/documentation/lux/test/coverage.lux b/stdlib/source/documentation/lux/test/coverage.lux
new file mode 100644
index 000000000..b443e9cbd
--- /dev/null
+++ b/stdlib/source/documentation/lux/test/coverage.lux
@@ -0,0 +1,20 @@
+(.require
+ [library
+ [lux (.except)
+ ["$" documentation]
+ [data
+ ["[0]" text (.only \n)
+ ["%" \\format (.only format)]]]]]
+ [\\library
+ ["[0]" /]])
+
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.Coverage)
+ ($.definition /.of)
+ ($.definition /.encoded)
+ ($.definition /.decoded)
+ ))
diff --git a/stdlib/source/documentation/lux/test/property.lux b/stdlib/source/documentation/lux/test/property.lux
new file mode 100644
index 000000000..b21fef1ec
--- /dev/null
+++ b/stdlib/source/documentation/lux/test/property.lux
@@ -0,0 +1,86 @@
+(.require
+ [library
+ [lux (.except)
+ ["$" documentation]
+ [data
+ ["[0]" text (.only \n)
+ ["%" \\format (.only format)]]]]]
+ [\\library
+ ["[0]" /]])
+
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "Property-based/generative testing.")
+
+ ($.definition /.must_try_test_at_least_once)
+ ($.definition /.error_during_execution)
+
+ ($.definition /.Test
+ "A test that relies on random data generation to thoroughly cover different scenarios.")
+
+ ($.definition /.and
+ "Sequencing combinator."
+ [(and left right)])
+
+ ($.definition /.context
+ "Adds a contextual description to a test's documentation."
+ [(context description)])
+
+ ($.definition /.failure
+ "A failing test, with a given error message.")
+
+ ($.definition /.success)
+
+ ($.definition /.test
+ "Check that a condition is #1, and fail with the given message otherwise."
+ [(test message condition)])
+
+ ($.definition /.lifted
+ ""
+ [(lifted message random)])
+
+ ($.definition /.Seed
+ "The seed value used for random testing (if that feature is used).")
+
+ ($.definition /.seed
+ (format "Execute the given test with a specific seed value."
+ \n "This allows you to reproduce a failing test case as many times as you want while debugging.")
+ [(seed value test)])
+
+ ($.definition /.times
+ (format "Allows executing a test several times."
+ \n "By doing this, it's possible to thoroughly test code with many different scenarios."
+ \n "This assumes that random data generation is being used in tests instead of fixed/constant inputs.")
+ [(times amount test)])
+
+ ($.definition /.run!
+ (format "Executes a test, and exits the program with either a successful or a failing exit code."
+ \n "WARNING: This procedure is only meant to be used in (program ...) forms.")
+ [(run! test)])
+
+ ($.definition /.coverage
+ (format "Specifies a test as covering one or more definitions."
+ \n "Adds to the test tally information to track which definitions have been tested.")
+ [(coverage [definition/0 definition/1 ,,, definition/N]
+ (is Bit
+ (some "computation")))])
+
+ ($.definition /.for
+ (format "Specifies a context for tests as covering one or more definitions."
+ \n "Adds to the test tally information to track which definitions have been tested.")
+ [(for [definition/0 definition/1 ,,, definition/N]
+ (is Test
+ some_test))])
+
+ ($.definition /.covering
+ (format "Specifies the module being covered by a test."
+ \n "Adds tracking information to the tally to know which exported definitions in the module need to be covered.")
+ [(covering .._
+ (is Test
+ some_test))])
+
+ ($.definition /.in_parallel
+ "Executes multiple tests in parallel (if the host platform supports it) to take advantage of multiple cores."
+ [(in_parallel tests)])
+ ))
diff --git a/stdlib/source/documentation/lux/test/tally.lux b/stdlib/source/documentation/lux/test/tally.lux
new file mode 100644
index 000000000..a13267544
--- /dev/null
+++ b/stdlib/source/documentation/lux/test/tally.lux
@@ -0,0 +1,26 @@
+(.require
+ [library
+ [lux (.except)
+ ["$" documentation]
+ [data
+ ["[0]" text (.only \n)
+ ["%" \\format (.only format)]]]]]
+ [\\library
+ ["[0]" /]])
+
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.Tally
+ "A record of successes and failures while executing tests.")
+
+ ($.definition /.and
+ ""
+ [(and left right)])
+
+ ($.definition /.empty)
+ ($.definition /.success)
+ ($.definition /.failure)
+ ))
diff --git a/stdlib/source/documentation/lux/test/unit.lux b/stdlib/source/documentation/lux/test/unit.lux
new file mode 100644
index 000000000..2b5e9441a
--- /dev/null
+++ b/stdlib/source/documentation/lux/test/unit.lux
@@ -0,0 +1,51 @@
+(.require
+ [library
+ [lux (.except)
+ ["$" documentation]
+ [data
+ ["[0]" text (.only \n)
+ ["%" \\format (.only format)]]]]]
+ [\\library
+ ["[0]" /]])
+
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "Unit testing.")
+
+ ($.definition /.Test
+ "An asynchronous operation that yields test results.")
+
+ ($.definition /.and
+ "Sequencing combinator."
+ [(and left right)])
+
+ ($.definition /.test
+ "Check that a condition is #1, and fail with the given message otherwise."
+ [(test message condition)])
+
+ ($.definition /.coverage
+ (format "Specifies a test as covering one or more definitions."
+ \n "Adds to the test tally information to track which definitions have been tested.")
+ [(coverage [definition/0 definition/1 ,,, definition/N]
+ (is Bit
+ (some "computation")))])
+
+ ($.definition /.for
+ (format "Specifies a context for tests as covering one or more definitions."
+ \n "Adds to the test tally information to track which definitions have been tested.")
+ [(for [definition/0 definition/1 ,,, definition/N]
+ (is Test
+ some_test))])
+
+ ($.definition /.covering
+ (format "Specifies the module being covered by a test."
+ \n "Adds tracking information to the tally to know which exported definitions in the module need to be covered.")
+ [(covering .._
+ (is Test
+ some_test))])
+
+ ($.definition /.context)
+ ($.definition /.success)
+ ($.definition /.failure)
+ ))
diff --git a/stdlib/source/documentation/lux/world.lux b/stdlib/source/documentation/lux/world.lux
index 2e3dd6945..9dde22d78 100644
--- a/stdlib/source/documentation/lux/world.lux
+++ b/stdlib/source/documentation/lux/world.lux
@@ -22,8 +22,8 @@
["[1][0]" time]
["[1][0]" locale]])
-(.def .public documentation
- (.List $.Module)
+(def .public documentation
+ (List $.Documentation)
(all list#composite
/console.documentation
/file.documentation
diff --git a/stdlib/source/documentation/lux/world/console.lux b/stdlib/source/documentation/lux/world/console.lux
index 19df25dc3..77e62fac9 100644
--- a/stdlib/source/documentation/lux/world/console.lux
+++ b/stdlib/source/documentation/lux/world/console.lux
@@ -10,28 +10,29 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- (`` (`` ($.module /._
- ""
- [($.definition /.async)
- (,, (for @.jvm (,, (these ($.definition /.cannot_open)
- ($.definition /.cannot_close)
- ($.definition /.default)))
- (,, (these))))
+(def .public documentation
+ (List $.Documentation)
+ (`` (`` (list ($.module /._
+ "")
- ($.definition (/.Console !)
- "An interface to console/terminal I/O.")
+ ($.definition /.async)
+ (,, (for @.jvm (,, (these ($.definition /.cannot_open)
+ ($.definition /.cannot_close)
+ ($.definition /.default)))
+ (,, (these))))
- ($.definition /.write_line
- "Writes the message on the console and appends a new-line/line-feed at the end."
- [(write_line message console)])
+ ($.definition (/.Console !)
+ "An interface to console/terminal I/O.")
- ($.definition (/.Mock s)
- (format "A mock/simulation of a console."
- \n "Useful for testing."))
+ ($.definition /.write_line
+ "Writes the message on the console and appends a new-line/line-feed at the end."
+ [(write_line message console)])
- ($.definition /.mock
- ""
- [(mock mock init)])]
- []))))
+ ($.definition (/.Mock s)
+ (format "A mock/simulation of a console."
+ \n "Useful for testing."))
+
+ ($.definition /.mock
+ ""
+ [(mock mock init)])
+ ))))
diff --git a/stdlib/source/documentation/lux/world/environment.lux b/stdlib/source/documentation/lux/world/environment.lux
index 8a94cc818..6aa8ccf55 100644
--- a/stdlib/source/documentation/lux/world/environment.lux
+++ b/stdlib/source/documentation/lux/world/environment.lux
@@ -4,55 +4,61 @@
["$" documentation]
[data
["[0]" text (.only \n)
- ["%" \\format (.only format)]]]]]
+ ["%" \\format (.only format)]]
+ [collection
+ ["[0]" list]]]]]
["[0]" \\parser]
[\\library
["[0]" /]])
-(.def \\parser
- (.List $.Module)
- ($.module \\parser._
- ""
- [($.definition \\parser.unknown_property)
-
- ($.definition \\parser.Property
- "A property in the environment.")
-
- ($.definition \\parser.Environment
- "An abstraction for environment variables of a program.")
-
- ($.definition (\\parser.Parser it)
- "A parser of environment variables of a program.")
-
- ($.definition \\parser.empty
- "An empty environment.")
-
- ($.definition \\parser.property
- ""
- [(property name)])
-
- ($.definition \\parser.result
- (format "Executes a parser against the given environment variables."
- \n "Does not check whether all environment variables were parsed, since they're usually an open set.")
- [(result parser environment)])]
- []))
-
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.unknown_environment_variable)
- ($.definition /.async)
- ($.definition /.default)
-
- ($.definition (/.Environment !)
- "Access to ambient environment data and the capacity to exit the program.")
-
- ($.definition /.environment
- "Assembles the environment variables available to the program."
- [(environment monad program)])
-
- ($.definition /.mock
- ""
- [(mock environment home directory)])]
- [..\\parser]))
+(def \\parser
+ (List $.Documentation)
+ (list ($.module \\parser._
+ "")
+
+ ($.definition \\parser.unknown_property)
+
+ ($.definition \\parser.Property
+ "A property in the environment.")
+
+ ($.definition \\parser.Environment
+ "An abstraction for environment variables of a program.")
+
+ ($.definition (\\parser.Parser it)
+ "A parser of environment variables of a program.")
+
+ ($.definition \\parser.empty
+ "An empty environment.")
+
+ ($.definition \\parser.property
+ ""
+ [(property name)])
+
+ ($.definition \\parser.result
+ (format "Executes a parser against the given environment variables."
+ \n "Does not check whether all environment variables were parsed, since they're usually an open set.")
+ [(result parser environment)])
+ ))
+
+(def .public documentation
+ (List $.Documentation)
+ (list.partial ($.module /._
+ "")
+
+ ($.definition /.unknown_environment_variable)
+ ($.definition /.async)
+ ($.definition /.default)
+
+ ($.definition (/.Environment !)
+ "Access to ambient environment data and the capacity to exit the program.")
+
+ ($.definition /.environment
+ "Assembles the environment variables available to the program."
+ [(environment monad program)])
+
+ ($.definition /.mock
+ ""
+ [(mock environment home directory)])
+
+ ..\\parser
+ ))
diff --git a/stdlib/source/documentation/lux/world/file.lux b/stdlib/source/documentation/lux/world/file.lux
index 1d9e7c065..d5df3bca6 100644
--- a/stdlib/source/documentation/lux/world/file.lux
+++ b/stdlib/source/documentation/lux/world/file.lux
@@ -4,7 +4,9 @@
["$" documentation]
[data
["[0]" text (.only \n)
- ["%" \\format (.only format)]]]
+ ["%" \\format (.only format)]]
+ [collection
+ ["[0]" list]]]
[meta
["@" target]]]]
[\\library
@@ -12,52 +14,55 @@
["[0]" /
["[1][0]" watch]])
-(.def .public documentation
- (.List $.Module)
- (`` (`` ($.module /._
- ""
- [($.definition /.async)
- ($.definition /.cannot_make_file)
- ($.definition /.cannot_find_file)
- ($.definition /.cannot_delete)
- ($.definition /.cannot_make_directory)
- ($.definition /.cannot_find_directory)
- (,, (for @.lua (,, (these))
- (,, (these ($.definition /.default)))))
-
- ($.definition /.Path
- "A path to a file or a directory in a file-system.")
-
- ($.definition (/.System !)
- "An interface to a file-system.")
-
- ($.definition /.parent
- "If a path represents a nested file/directory, extracts its parent directory."
- [(parent fs path)])
-
- ($.definition /.name
- "The un-nested name of a file/directory."
- [(name fs path)])
-
- ($.definition /.rooted
- "A nested path for a file/directory, given a root/parent path and a file/directory name within it."
- [(rooted fs parent child)])
-
- ($.definition /.exists?
- "Checks if either a file or a directory exists at the given path."
- [(exists? monad fs path)])
-
- ($.definition /.mock
- (format "A purely in-memory simulation of a file-system."
- \n "Useful for testing.")
- [(mock separator)])
-
- ($.definition /.make_directories
- (format "Creates the directory specified by the given path."
- \n "Also, creates every super-directory necessary to make the given path valid.")
- [(make_directories monad fs path)])
-
- ($.definition /.make_file
- "Creates a new file with the given content if-and-only-if the file does not already exist."
- [(make_file monad fs content path)])]
- [/watch.documentation]))))
+(def .public documentation
+ (List $.Documentation)
+ (`` (`` (list.partial ($.module /._
+ "")
+
+ ($.definition /.async)
+ ($.definition /.cannot_make_file)
+ ($.definition /.cannot_find_file)
+ ($.definition /.cannot_delete)
+ ($.definition /.cannot_make_directory)
+ ($.definition /.cannot_find_directory)
+ (,, (for @.lua (,, (these))
+ (,, (these ($.definition /.default)))))
+
+ ($.definition /.Path
+ "A path to a file or a directory in a file-system.")
+
+ ($.definition (/.System !)
+ "An interface to a file-system.")
+
+ ($.definition /.parent
+ "If a path represents a nested file/directory, extracts its parent directory."
+ [(parent fs path)])
+
+ ($.definition /.name
+ "The un-nested name of a file/directory."
+ [(name fs path)])
+
+ ($.definition /.rooted
+ "A nested path for a file/directory, given a root/parent path and a file/directory name within it."
+ [(rooted fs parent child)])
+
+ ($.definition /.exists?
+ "Checks if either a file or a directory exists at the given path."
+ [(exists? monad fs path)])
+
+ ($.definition /.mock
+ (format "A purely in-memory simulation of a file-system."
+ \n "Useful for testing.")
+ [(mock separator)])
+
+ ($.definition /.make_directories
+ (format "Creates the directory specified by the given path."
+ \n "Also, creates every super-directory necessary to make the given path valid.")
+ [(make_directories monad fs path)])
+
+ ($.definition /.make_file
+ "Creates a new file with the given content if-and-only-if the file does not already exist."
+ [(make_file monad fs content path)])
+
+ /watch.documentation
+ ))))
diff --git a/stdlib/source/documentation/lux/world/file/watch.lux b/stdlib/source/documentation/lux/world/file/watch.lux
index 397336094..7ef28a451 100644
--- a/stdlib/source/documentation/lux/world/file/watch.lux
+++ b/stdlib/source/documentation/lux/world/file/watch.lux
@@ -10,41 +10,42 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- (`` (`` ($.module /._
- ""
- [($.definition /.creation)
- ($.definition /.creation?)
- ($.definition /.modification)
- ($.definition /.modification?)
- ($.definition /.deletion)
- ($.definition /.deletion?)
- ($.definition /.all)
- ($.definition /.not_being_watched)
- ($.definition /.cannot_poll_a_non_existent_directory)
-
- ($.definition /.Concern
- "A particular concern to watch-out for.")
+(def .public documentation
+ (List $.Documentation)
+ (`` (`` (list ($.module /._
+ "")
- ($.definition /.and
- ""
- [(and left right)])
+ ($.definition /.creation)
+ ($.definition /.creation?)
+ ($.definition /.modification)
+ ($.definition /.modification?)
+ ($.definition /.deletion)
+ ($.definition /.deletion?)
+ ($.definition /.all)
+ ($.definition /.not_being_watched)
+ ($.definition /.cannot_poll_a_non_existent_directory)
+
+ ($.definition /.Concern
+ "A particular concern to watch-out for.")
- ($.definition (/.Watcher !)
- "Machinery for watching a file-system for changes to files and directories.")
+ ($.definition /.and
+ ""
+ [(and left right)])
- ($.definition /.polling
- (format "A simple watcher that works for any file-system."
- "Polls files and directories to detect changes.")
- [(polling fs)])
+ ($.definition (/.Watcher !)
+ "Machinery for watching a file-system for changes to files and directories.")
- ($.definition /.mock
- (format "A fake/emulated watcher."
- \n "Must be given a path separator for the file-system.")
- [(mock separator)])
+ ($.definition /.polling
+ (format "A simple watcher that works for any file-system."
+ "Polls files and directories to detect changes.")
+ [(polling fs)])
- (,, (for @.jvm (,, (these ($.definition /.default
- "The default watcher for the default file-system.")))
- (,, (these))))]
- []))))
+ ($.definition /.mock
+ (format "A fake/emulated watcher."
+ \n "Must be given a path separator for the file-system.")
+ [(mock separator)])
+
+ (,, (for @.jvm (,, (these ($.definition /.default
+ "The default watcher for the default file-system.")))
+ (,, (these))))
+ ))))
diff --git a/stdlib/source/documentation/lux/world/input/keyboard.lux b/stdlib/source/documentation/lux/world/input/keyboard.lux
index 277acb971..b6fa9b392 100644
--- a/stdlib/source/documentation/lux/world/input/keyboard.lux
+++ b/stdlib/source/documentation/lux/world/input/keyboard.lux
@@ -8,98 +8,99 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.back_space)
- ($.definition /.enter)
- ($.definition /.shift)
- ($.definition /.control)
- ($.definition /.alt)
- ($.definition /.caps_lock)
- ($.definition /.escape)
- ($.definition /.space)
- ($.definition /.page_up)
- ($.definition /.page_down)
- ($.definition /.end)
- ($.definition /.home)
- ($.definition /.left)
- ($.definition /.up)
- ($.definition /.right)
- ($.definition /.down)
- ($.definition /.a)
- ($.definition /.b)
- ($.definition /.c)
- ($.definition /.d)
- ($.definition /.e)
- ($.definition /.f)
- ($.definition /.g)
- ($.definition /.h)
- ($.definition /.i)
- ($.definition /.j)
- ($.definition /.k)
- ($.definition /.l)
- ($.definition /.m)
- ($.definition /.n)
- ($.definition /.o)
- ($.definition /.p)
- ($.definition /.q)
- ($.definition /.r)
- ($.definition /.s)
- ($.definition /.t)
- ($.definition /.u)
- ($.definition /.v)
- ($.definition /.w)
- ($.definition /.x)
- ($.definition /.y)
- ($.definition /.z)
- ($.definition /.num_pad_0)
- ($.definition /.num_pad_1)
- ($.definition /.num_pad_2)
- ($.definition /.num_pad_3)
- ($.definition /.num_pad_4)
- ($.definition /.num_pad_5)
- ($.definition /.num_pad_6)
- ($.definition /.num_pad_7)
- ($.definition /.num_pad_8)
- ($.definition /.num_pad_9)
- ($.definition /.delete)
- ($.definition /.num_lock)
- ($.definition /.scroll_lock)
- ($.definition /.print_screen)
- ($.definition /.insert)
- ($.definition /.windows)
- ($.definition /.f1)
- ($.definition /.f2)
- ($.definition /.f3)
- ($.definition /.f4)
- ($.definition /.f5)
- ($.definition /.f6)
- ($.definition /.f7)
- ($.definition /.f8)
- ($.definition /.f9)
- ($.definition /.f10)
- ($.definition /.f11)
- ($.definition /.f12)
- ($.definition /.f13)
- ($.definition /.f14)
- ($.definition /.f15)
- ($.definition /.f16)
- ($.definition /.f17)
- ($.definition /.f18)
- ($.definition /.f19)
- ($.definition /.f20)
- ($.definition /.f21)
- ($.definition /.f22)
- ($.definition /.f23)
- ($.definition /.f24)
- ($.definition /.release)
- ($.definition /.press)
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition /.Key
- "A key from a keyboard, identify by a numeric ID.")
+ ($.definition /.back_space)
+ ($.definition /.enter)
+ ($.definition /.shift)
+ ($.definition /.control)
+ ($.definition /.alt)
+ ($.definition /.caps_lock)
+ ($.definition /.escape)
+ ($.definition /.space)
+ ($.definition /.page_up)
+ ($.definition /.page_down)
+ ($.definition /.end)
+ ($.definition /.home)
+ ($.definition /.left)
+ ($.definition /.up)
+ ($.definition /.right)
+ ($.definition /.down)
+ ($.definition /.a)
+ ($.definition /.b)
+ ($.definition /.c)
+ ($.definition /.d)
+ ($.definition /.e)
+ ($.definition /.f)
+ ($.definition /.g)
+ ($.definition /.h)
+ ($.definition /.i)
+ ($.definition /.j)
+ ($.definition /.k)
+ ($.definition /.l)
+ ($.definition /.m)
+ ($.definition /.n)
+ ($.definition /.o)
+ ($.definition /.p)
+ ($.definition /.q)
+ ($.definition /.r)
+ ($.definition /.s)
+ ($.definition /.t)
+ ($.definition /.u)
+ ($.definition /.v)
+ ($.definition /.w)
+ ($.definition /.x)
+ ($.definition /.y)
+ ($.definition /.z)
+ ($.definition /.num_pad_0)
+ ($.definition /.num_pad_1)
+ ($.definition /.num_pad_2)
+ ($.definition /.num_pad_3)
+ ($.definition /.num_pad_4)
+ ($.definition /.num_pad_5)
+ ($.definition /.num_pad_6)
+ ($.definition /.num_pad_7)
+ ($.definition /.num_pad_8)
+ ($.definition /.num_pad_9)
+ ($.definition /.delete)
+ ($.definition /.num_lock)
+ ($.definition /.scroll_lock)
+ ($.definition /.print_screen)
+ ($.definition /.insert)
+ ($.definition /.windows)
+ ($.definition /.f1)
+ ($.definition /.f2)
+ ($.definition /.f3)
+ ($.definition /.f4)
+ ($.definition /.f5)
+ ($.definition /.f6)
+ ($.definition /.f7)
+ ($.definition /.f8)
+ ($.definition /.f9)
+ ($.definition /.f10)
+ ($.definition /.f11)
+ ($.definition /.f12)
+ ($.definition /.f13)
+ ($.definition /.f14)
+ ($.definition /.f15)
+ ($.definition /.f16)
+ ($.definition /.f17)
+ ($.definition /.f18)
+ ($.definition /.f19)
+ ($.definition /.f20)
+ ($.definition /.f21)
+ ($.definition /.f22)
+ ($.definition /.f23)
+ ($.definition /.f24)
+ ($.definition /.release)
+ ($.definition /.press)
- ($.definition /.Press
- "A key-press for a key.")]
- []))
+ ($.definition /.Key
+ "A key from a keyboard, identify by a numeric ID.")
+
+ ($.definition /.Press
+ "A key-press for a key.")
+ ))
diff --git a/stdlib/source/documentation/lux/world/locale.lux b/stdlib/source/documentation/lux/world/locale.lux
index 92113b53a..6dc04bd77 100644
--- a/stdlib/source/documentation/lux/world/locale.lux
+++ b/stdlib/source/documentation/lux/world/locale.lux
@@ -1,31 +1,36 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text
["%" \\format (.only format)]]
[collection
- ["[0]" list]]]]]
+ ["[0]" list (.use "[1]#[0]" monoid)]]]]]
["[0]" /
["[1][0]" language]
["[1][0]" territory]]
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.code)
- ($.definition /.hash)
- ($.definition /.equivalence)
+(def .public documentation
+ (List $.Documentation)
+ (list.partial ($.module /._
+ "")
- ($.definition /.Locale
- "A description of a locale; with territory, (optional) language, and (optional) text-encoding.")
+ ($.definition /.code)
+ ($.definition /.hash)
+ ($.definition /.equivalence)
- ($.definition /.locale
- ""
- [(locale language territory encoding)])]
- [/language.documentation
- /territory.documentation]))
+ ($.definition /.Locale
+ "A description of a locale; with territory, (optional) language, and (optional) text-encoding.")
+
+ ($.definition /.locale
+ ""
+ [(locale language territory encoding)])
+
+ (all list#composite
+ /language.documentation
+ /territory.documentation
+ )
+ ))
diff --git a/stdlib/source/documentation/lux/world/locale/language.lux b/stdlib/source/documentation/lux/world/locale/language.lux
index b59bb25b4..615e56ae7 100644
--- a/stdlib/source/documentation/lux/world/locale/language.lux
+++ b/stdlib/source/documentation/lux/world/locale/language.lux
@@ -1,659 +1,663 @@
(.require
[library
- [lux (.except char)
+ [lux (.except)
["$" documentation]
[data
[text
["%" \\format (.only format)]]
[collection
- ["[0]" list]]]]]
+ ["[0]" list (.use "[1]#[0]" monoid)]]]]]
[\\library
["[0]" /]])
(def items/~
- (list.together
- (list ($.definition /.uncoded)
- ($.definition /.multiple)
- ($.definition /.undetermined)
- ($.definition /.not_applicable))))
+ (List $.Documentation)
+ (list ($.definition /.uncoded)
+ ($.definition /.multiple)
+ ($.definition /.undetermined)
+ ($.definition /.not_applicable)))
(def items/a
- (list.together
- (list ($.definition /.afar)
- ($.definition /.abkhazian)
- ($.definition /.achinese)
- ($.definition /.acoli)
- ($.definition /.adangme)
- ($.definition /.adyghe)
- ($.definition /.afro_asiatic)
- ($.definition /.afrihili)
- ($.definition /.afrikaans)
- ($.definition /.ainu)
- ($.definition /.akan)
- ($.definition /.akkadian)
- ($.definition /.aleut)
- ($.definition /.algonquian)
- ($.definition /.southern_altai)
- ($.definition /.amharic)
- ($.definition /.old_english)
- ($.definition /.angika)
- ($.definition /.apache)
- ($.definition /.arabic)
- ($.definition /.official_aramaic)
- ($.definition /.imperial_aramaic)
- ($.definition /.aragonese)
- ($.definition /.mapudungun)
- ($.definition /.arapaho)
- ($.definition /.artificial)
- ($.definition /.arawak)
- ($.definition /.assamese)
- ($.definition /.asturian)
- ($.definition /.bable)
- ($.definition /.leonese)
- ($.definition /.asturleonese)
- ($.definition /.athapascan)
- ($.definition /.australian)
- ($.definition /.avaric)
- ($.definition /.avestan)
- ($.definition /.awadhi)
- ($.definition /.aymara)
- ($.definition /.azerbaijani))))
+ (List $.Documentation)
+ (list ($.definition /.afar)
+ ($.definition /.abkhazian)
+ ($.definition /.achinese)
+ ($.definition /.acoli)
+ ($.definition /.adangme)
+ ($.definition /.adyghe)
+ ($.definition /.afro_asiatic)
+ ($.definition /.afrihili)
+ ($.definition /.afrikaans)
+ ($.definition /.ainu)
+ ($.definition /.akan)
+ ($.definition /.akkadian)
+ ($.definition /.aleut)
+ ($.definition /.algonquian)
+ ($.definition /.southern_altai)
+ ($.definition /.amharic)
+ ($.definition /.old_english)
+ ($.definition /.angika)
+ ($.definition /.apache)
+ ($.definition /.arabic)
+ ($.definition /.official_aramaic)
+ ($.definition /.imperial_aramaic)
+ ($.definition /.aragonese)
+ ($.definition /.mapudungun)
+ ($.definition /.arapaho)
+ ($.definition /.artificial)
+ ($.definition /.arawak)
+ ($.definition /.assamese)
+ ($.definition /.asturian)
+ ($.definition /.bable)
+ ($.definition /.leonese)
+ ($.definition /.asturleonese)
+ ($.definition /.athapascan)
+ ($.definition /.australian)
+ ($.definition /.avaric)
+ ($.definition /.avestan)
+ ($.definition /.awadhi)
+ ($.definition /.aymara)
+ ($.definition /.azerbaijani)))
(def items/b
- (list.together
- (list ($.definition /.banda)
- ($.definition /.bamileke)
- ($.definition /.bashkir)
- ($.definition /.baluchi)
- ($.definition /.bambara)
- ($.definition /.balinese)
- ($.definition /.basa)
- ($.definition /.baltic)
- ($.definition /.beja)
- ($.definition /.belarusian)
- ($.definition /.bemba)
- ($.definition /.bengali)
- ($.definition /.berber)
- ($.definition /.bhojpuri)
- ($.definition /.bihari)
- ($.definition /.bikol)
- ($.definition /.bini)
- ($.definition /.edo)
- ($.definition /.bislama)
- ($.definition /.siksika)
- ($.definition /.bantu)
- ($.definition /.tibetan)
- ($.definition /.bosnian)
- ($.definition /.braj)
- ($.definition /.breton)
- ($.definition /.batak)
- ($.definition /.buriat)
- ($.definition /.buginese)
- ($.definition /.bulgarian)
- ($.definition /.blin)
- ($.definition /.bilin))))
+ (List $.Documentation)
+ (list ($.definition /.banda)
+ ($.definition /.bamileke)
+ ($.definition /.bashkir)
+ ($.definition /.baluchi)
+ ($.definition /.bambara)
+ ($.definition /.balinese)
+ ($.definition /.basa)
+ ($.definition /.baltic)
+ ($.definition /.beja)
+ ($.definition /.belarusian)
+ ($.definition /.bemba)
+ ($.definition /.bengali)
+ ($.definition /.berber)
+ ($.definition /.bhojpuri)
+ ($.definition /.bihari)
+ ($.definition /.bikol)
+ ($.definition /.bini)
+ ($.definition /.edo)
+ ($.definition /.bislama)
+ ($.definition /.siksika)
+ ($.definition /.bantu)
+ ($.definition /.tibetan)
+ ($.definition /.bosnian)
+ ($.definition /.braj)
+ ($.definition /.breton)
+ ($.definition /.batak)
+ ($.definition /.buriat)
+ ($.definition /.buginese)
+ ($.definition /.bulgarian)
+ ($.definition /.blin)
+ ($.definition /.bilin)))
(def items/c
- (list.together
- (list ($.definition /.caddo)
- ($.definition /.central_american_indian)
- ($.definition /.galibi_carib)
- ($.definition /.catalan)
- ($.definition /.valencian)
- ($.definition /.caucasian)
- ($.definition /.cebuano)
- ($.definition /.celtic)
- ($.definition /.czech)
- ($.definition /.chamorro)
- ($.definition /.chibcha)
- ($.definition /.chechen)
- ($.definition /.chagatai)
- ($.definition /.chuukese)
- ($.definition /.mari)
- ($.definition /.chinook)
- ($.definition /.choctaw)
- ($.definition /.chipewyan)
- ($.definition /.cherokee)
- ($.definition /.church_slavic)
- ($.definition /.old_slavonic)
- ($.definition /.church_slavonic)
- ($.definition /.old_bulgarian)
- ($.definition /.old_church_slavonic)
- ($.definition /.chuvash)
- ($.definition /.cheyenne)
- ($.definition /.chamic)
- ($.definition /.montenegrin)
- ($.definition /.coptic)
- ($.definition /.cornish)
- ($.definition /.corsican)
- ($.definition /.creoles_and_pidgins/english)
- ($.definition /.creoles_and_pidgins/french)
- ($.definition /.creoles_and_pidgins/portuguese)
- ($.definition /.cree)
- ($.definition /.crimean)
- ($.definition /.creoles_and_pidgins)
- ($.definition /.kashubian)
- ($.definition /.cushitic)
- ($.definition /.welsh))))
+ (List $.Documentation)
+ (list ($.definition /.caddo)
+ ($.definition /.central_american_indian)
+ ($.definition /.galibi_carib)
+ ($.definition /.catalan)
+ ($.definition /.valencian)
+ ($.definition /.caucasian)
+ ($.definition /.cebuano)
+ ($.definition /.celtic)
+ ($.definition /.czech)
+ ($.definition /.chamorro)
+ ($.definition /.chibcha)
+ ($.definition /.chechen)
+ ($.definition /.chagatai)
+ ($.definition /.chuukese)
+ ($.definition /.mari)
+ ($.definition /.chinook)
+ ($.definition /.choctaw)
+ ($.definition /.chipewyan)
+ ($.definition /.cherokee)
+ ($.definition /.church_slavic)
+ ($.definition /.old_slavonic)
+ ($.definition /.church_slavonic)
+ ($.definition /.old_bulgarian)
+ ($.definition /.old_church_slavonic)
+ ($.definition /.chuvash)
+ ($.definition /.cheyenne)
+ ($.definition /.chamic)
+ ($.definition /.montenegrin)
+ ($.definition /.coptic)
+ ($.definition /.cornish)
+ ($.definition /.corsican)
+ ($.definition /.creoles_and_pidgins/english)
+ ($.definition /.creoles_and_pidgins/french)
+ ($.definition /.creoles_and_pidgins/portuguese)
+ ($.definition /.cree)
+ ($.definition /.crimean)
+ ($.definition /.creoles_and_pidgins)
+ ($.definition /.kashubian)
+ ($.definition /.cushitic)
+ ($.definition /.welsh)))
(def items/d
- (list.together
- (list ($.definition /.dakota)
- ($.definition /.danish)
- ($.definition /.dargwa)
- ($.definition /.land_dayak)
- ($.definition /.delaware)
- ($.definition /.slavey)
- ($.definition /.german)
- ($.definition /.dogrib)
- ($.definition /.dinka)
- ($.definition /.dhivehi)
- ($.definition /.maldivian)
- ($.definition /.dogri)
- ($.definition /.dravidian)
- ($.definition /.lower_sorbian)
- ($.definition /.duala)
- ($.definition /.middle_dutch)
- ($.definition /.dyula)
- ($.definition /.dzongkha))))
+ (List $.Documentation)
+ (list ($.definition /.dakota)
+ ($.definition /.danish)
+ ($.definition /.dargwa)
+ ($.definition /.land_dayak)
+ ($.definition /.delaware)
+ ($.definition /.slavey)
+ ($.definition /.german)
+ ($.definition /.dogrib)
+ ($.definition /.dinka)
+ ($.definition /.dhivehi)
+ ($.definition /.maldivian)
+ ($.definition /.dogri)
+ ($.definition /.dravidian)
+ ($.definition /.lower_sorbian)
+ ($.definition /.duala)
+ ($.definition /.middle_dutch)
+ ($.definition /.dyula)
+ ($.definition /.dzongkha)))
(def items/e
- (list.together
- (list ($.definition /.efik)
- ($.definition /.egyptian)
- ($.definition /.ekajuk)
- ($.definition /.greek)
- ($.definition /.elamite)
- ($.definition /.english)
- ($.definition /.middle_english)
- ($.definition /.esperanto)
- ($.definition /.estonian)
- ($.definition /.basque)
- ($.definition /.ewe)
- ($.definition /.ewondo))))
+ (List $.Documentation)
+ (list ($.definition /.efik)
+ ($.definition /.egyptian)
+ ($.definition /.ekajuk)
+ ($.definition /.greek)
+ ($.definition /.elamite)
+ ($.definition /.english)
+ ($.definition /.middle_english)
+ ($.definition /.esperanto)
+ ($.definition /.estonian)
+ ($.definition /.basque)
+ ($.definition /.ewe)
+ ($.definition /.ewondo)))
(def items/f
- (list.together
- (list ($.definition /.fang)
- ($.definition /.faroese)
- ($.definition /.persian)
- ($.definition /.fanti)
- ($.definition /.fijian)
- ($.definition /.filipino)
- ($.definition /.finnish)
- ($.definition /.finno_ugrian)
- ($.definition /.fon)
- ($.definition /.french)
- ($.definition /.middle_french)
- ($.definition /.old_french)
- ($.definition /.northern_frisian)
- ($.definition /.eastern_frisian)
- ($.definition /.western_frisian)
- ($.definition /.fulah)
- ($.definition /.friulian))))
+ (List $.Documentation)
+ (list ($.definition /.fang)
+ ($.definition /.faroese)
+ ($.definition /.persian)
+ ($.definition /.fanti)
+ ($.definition /.fijian)
+ ($.definition /.filipino)
+ ($.definition /.finnish)
+ ($.definition /.finno_ugrian)
+ ($.definition /.fon)
+ ($.definition /.french)
+ ($.definition /.middle_french)
+ ($.definition /.old_french)
+ ($.definition /.northern_frisian)
+ ($.definition /.eastern_frisian)
+ ($.definition /.western_frisian)
+ ($.definition /.fulah)
+ ($.definition /.friulian)))
(def items/g
- (list.together
- (list ($.definition /.ga)
- ($.definition /.gayo)
- ($.definition /.gbaya)
- ($.definition /.germanic)
- ($.definition /.geez)
- ($.definition /.gilbertese)
- ($.definition /.gaelic)
- ($.definition /.irish)
- ($.definition /.galician)
- ($.definition /.manx)
- ($.definition /.middle_high_german)
- ($.definition /.old_high_german)
- ($.definition /.gondi)
- ($.definition /.gorontalo)
- ($.definition /.gothic)
- ($.definition /.grebo)
- ($.definition /.ancient_greek)
- ($.definition /.guarani)
- ($.definition /.swiss_german)
- ($.definition /.alemannic)
- ($.definition /.alsatian)
- ($.definition /.gujarati)
- ($.definition /.gwich'in))))
+ (List $.Documentation)
+ (list ($.definition /.ga)
+ ($.definition /.gayo)
+ ($.definition /.gbaya)
+ ($.definition /.germanic)
+ ($.definition /.geez)
+ ($.definition /.gilbertese)
+ ($.definition /.gaelic)
+ ($.definition /.irish)
+ ($.definition /.galician)
+ ($.definition /.manx)
+ ($.definition /.middle_high_german)
+ ($.definition /.old_high_german)
+ ($.definition /.gondi)
+ ($.definition /.gorontalo)
+ ($.definition /.gothic)
+ ($.definition /.grebo)
+ ($.definition /.ancient_greek)
+ ($.definition /.guarani)
+ ($.definition /.swiss_german)
+ ($.definition /.alemannic)
+ ($.definition /.alsatian)
+ ($.definition /.gujarati)
+ ($.definition /.gwich'in)))
(def items/h
- (list.together
- (list ($.definition /.haida)
- ($.definition /.haitian)
- ($.definition /.hausa)
- ($.definition /.hawaiian)
- ($.definition /.hebrew)
- ($.definition /.herero)
- ($.definition /.hiligaynon)
- ($.definition /.himachali)
- ($.definition /.hindi)
- ($.definition /.hittite)
- ($.definition /.hmong)
- ($.definition /.hiri_motu)
- ($.definition /.croatian)
- ($.definition /.upper_sorbian)
- ($.definition /.hungarian)
- ($.definition /.hupa)
- ($.definition /.armenian))))
+ (List $.Documentation)
+ (list ($.definition /.haida)
+ ($.definition /.haitian)
+ ($.definition /.hausa)
+ ($.definition /.hawaiian)
+ ($.definition /.hebrew)
+ ($.definition /.herero)
+ ($.definition /.hiligaynon)
+ ($.definition /.himachali)
+ ($.definition /.hindi)
+ ($.definition /.hittite)
+ ($.definition /.hmong)
+ ($.definition /.hiri_motu)
+ ($.definition /.croatian)
+ ($.definition /.upper_sorbian)
+ ($.definition /.hungarian)
+ ($.definition /.hupa)
+ ($.definition /.armenian)))
(def items/i
- (list.together
- (list ($.definition /.iban)
- ($.definition /.igbo)
- ($.definition /.ido)
- ($.definition /.sichuan_yi)
- ($.definition /.nuosu)
- ($.definition /.ijo)
- ($.definition /.inuktitut)
- ($.definition /.interlingue)
- ($.definition /.iloko)
- ($.definition /.interlingua)
- ($.definition /.indic)
- ($.definition /.indonesian)
- ($.definition /.indo_european)
- ($.definition /.ingush)
- ($.definition /.inupiaq)
- ($.definition /.iranian)
- ($.definition /.iroquoian)
- ($.definition /.icelandic)
- ($.definition /.italian))))
+ (List $.Documentation)
+ (list ($.definition /.iban)
+ ($.definition /.igbo)
+ ($.definition /.ido)
+ ($.definition /.sichuan_yi)
+ ($.definition /.nuosu)
+ ($.definition /.ijo)
+ ($.definition /.inuktitut)
+ ($.definition /.interlingue)
+ ($.definition /.iloko)
+ ($.definition /.interlingua)
+ ($.definition /.indic)
+ ($.definition /.indonesian)
+ ($.definition /.indo_european)
+ ($.definition /.ingush)
+ ($.definition /.inupiaq)
+ ($.definition /.iranian)
+ ($.definition /.iroquoian)
+ ($.definition /.icelandic)
+ ($.definition /.italian)))
(def items/j
- (list.together
- (list ($.definition /.javanese)
- ($.definition /.lojban)
- ($.definition /.japanese)
- ($.definition /.judeo_persian)
- ($.definition /.judeo_arabic))))
+ (List $.Documentation)
+ (list ($.definition /.javanese)
+ ($.definition /.lojban)
+ ($.definition /.japanese)
+ ($.definition /.judeo_persian)
+ ($.definition /.judeo_arabic)))
(def items/k
- (list.together
- (list ($.definition /.kara_kalpak)
- ($.definition /.kabyle)
- ($.definition /.kachin)
- ($.definition /.jingpho)
- ($.definition /.kalaallisut)
- ($.definition /.greenlandic)
- ($.definition /.kamba)
- ($.definition /.kannada)
- ($.definition /.karen)
- ($.definition /.kashmiri)
- ($.definition /.georgian)
- ($.definition /.kanuri)
- ($.definition /.kawi)
- ($.definition /.kazakh)
- ($.definition /.kabardian)
- ($.definition /.khasi)
- ($.definition /.khoisan)
- ($.definition /.central_khmer)
- ($.definition /.khotanese)
- ($.definition /.sakan)
- ($.definition /.gikuyu)
- ($.definition /.kinyarwanda)
- ($.definition /.kyrgyz)
- ($.definition /.kimbundu)
- ($.definition /.konkani)
- ($.definition /.komi)
- ($.definition /.kongo)
- ($.definition /.korean)
- ($.definition /.kosraean)
- ($.definition /.kpelle)
- ($.definition /.karachay_balkar)
- ($.definition /.karelian)
- ($.definition /.kru)
- ($.definition /.kurukh)
- ($.definition /.kwanyama)
- ($.definition /.kumyk)
- ($.definition /.kurdish)
- ($.definition /.kutenai))))
+ (List $.Documentation)
+ (list ($.definition /.kara_kalpak)
+ ($.definition /.kabyle)
+ ($.definition /.kachin)
+ ($.definition /.jingpho)
+ ($.definition /.kalaallisut)
+ ($.definition /.greenlandic)
+ ($.definition /.kamba)
+ ($.definition /.kannada)
+ ($.definition /.karen)
+ ($.definition /.kashmiri)
+ ($.definition /.georgian)
+ ($.definition /.kanuri)
+ ($.definition /.kawi)
+ ($.definition /.kazakh)
+ ($.definition /.kabardian)
+ ($.definition /.khasi)
+ ($.definition /.khoisan)
+ ($.definition /.central_khmer)
+ ($.definition /.khotanese)
+ ($.definition /.sakan)
+ ($.definition /.gikuyu)
+ ($.definition /.kinyarwanda)
+ ($.definition /.kyrgyz)
+ ($.definition /.kimbundu)
+ ($.definition /.konkani)
+ ($.definition /.komi)
+ ($.definition /.kongo)
+ ($.definition /.korean)
+ ($.definition /.kosraean)
+ ($.definition /.kpelle)
+ ($.definition /.karachay_balkar)
+ ($.definition /.karelian)
+ ($.definition /.kru)
+ ($.definition /.kurukh)
+ ($.definition /.kwanyama)
+ ($.definition /.kumyk)
+ ($.definition /.kurdish)
+ ($.definition /.kutenai)))
(def items/l
- (list.together
- (list ($.definition /.ladino)
- ($.definition /.lahnda)
- ($.definition /.lamba)
- ($.definition /.lao)
- ($.definition /.latin)
- ($.definition /.latvian)
- ($.definition /.lezghian)
- ($.definition /.limburgan)
- ($.definition /.lingala)
- ($.definition /.lithuanian)
- ($.definition /.mongo)
- ($.definition /.lozi)
- ($.definition /.luxembourgish)
- ($.definition /.luba_lulua)
- ($.definition /.luba_katanga)
- ($.definition /.ganda)
- ($.definition /.luiseno)
- ($.definition /.lunda)
- ($.definition /.luo)
- ($.definition /.lushai))))
+ (List $.Documentation)
+ (list ($.definition /.ladino)
+ ($.definition /.lahnda)
+ ($.definition /.lamba)
+ ($.definition /.lao)
+ ($.definition /.latin)
+ ($.definition /.latvian)
+ ($.definition /.lezghian)
+ ($.definition /.limburgan)
+ ($.definition /.lingala)
+ ($.definition /.lithuanian)
+ ($.definition /.mongo)
+ ($.definition /.lozi)
+ ($.definition /.luxembourgish)
+ ($.definition /.luba_lulua)
+ ($.definition /.luba_katanga)
+ ($.definition /.ganda)
+ ($.definition /.luiseno)
+ ($.definition /.lunda)
+ ($.definition /.luo)
+ ($.definition /.lushai)))
(def items/m
- (list.together
- (list ($.definition /.madurese)
- ($.definition /.magahi)
- ($.definition /.marshallese)
- ($.definition /.maithili)
- ($.definition /.makasar)
- ($.definition /.malayalam)
- ($.definition /.mandingo)
- ($.definition /.austronesian)
- ($.definition /.marathi)
- ($.definition /.masai)
- ($.definition /.moksha)
- ($.definition /.mandar)
- ($.definition /.mende)
- ($.definition /.middle_irish)
- ($.definition /.mi'kmaq)
- ($.definition /.micmac)
- ($.definition /.minangkabau)
- ($.definition /.macedonian)
- ($.definition /.mon_khmer)
- ($.definition /.malagasy)
- ($.definition /.maltese)
- ($.definition /.manchu)
- ($.definition /.manipuri)
- ($.definition /.manobo)
- ($.definition /.mohawk)
- ($.definition /.mongolian)
- ($.definition /.mossi)
- ($.definition /.maori)
- ($.definition /.malay)
- ($.definition /.munda)
- ($.definition /.creek)
- ($.definition /.mirandese)
- ($.definition /.marwari)
- ($.definition /.burmese)
- ($.definition /.mayan)
- ($.definition /.erzya))))
+ (List $.Documentation)
+ (list ($.definition /.madurese)
+ ($.definition /.magahi)
+ ($.definition /.marshallese)
+ ($.definition /.maithili)
+ ($.definition /.makasar)
+ ($.definition /.malayalam)
+ ($.definition /.mandingo)
+ ($.definition /.austronesian)
+ ($.definition /.marathi)
+ ($.definition /.masai)
+ ($.definition /.moksha)
+ ($.definition /.mandar)
+ ($.definition /.mende)
+ ($.definition /.middle_irish)
+ ($.definition /.mi'kmaq)
+ ($.definition /.micmac)
+ ($.definition /.minangkabau)
+ ($.definition /.macedonian)
+ ($.definition /.mon_khmer)
+ ($.definition /.malagasy)
+ ($.definition /.maltese)
+ ($.definition /.manchu)
+ ($.definition /.manipuri)
+ ($.definition /.manobo)
+ ($.definition /.mohawk)
+ ($.definition /.mongolian)
+ ($.definition /.mossi)
+ ($.definition /.maori)
+ ($.definition /.malay)
+ ($.definition /.munda)
+ ($.definition /.creek)
+ ($.definition /.mirandese)
+ ($.definition /.marwari)
+ ($.definition /.burmese)
+ ($.definition /.mayan)
+ ($.definition /.erzya)))
(def items/n
- (list.together
- (list ($.definition /.nahuatl)
- ($.definition /.north_american_indian)
- ($.definition /.neapolitan)
- ($.definition /.nauru)
- ($.definition /.navajo)
- ($.definition /.south_ndebele)
- ($.definition /.north_ndebele)
- ($.definition /.ndonga)
- ($.definition /.low_german)
- ($.definition /.nepali)
- ($.definition /.newari)
- ($.definition /.nepal_bhasa)
- ($.definition /.nias)
- ($.definition /.niger_kordofanian)
- ($.definition /.niuean)
- ($.definition /.dutch)
- ($.definition /.flemish)
- ($.definition /.nynorsk)
- ($.definition /.bokmal)
- ($.definition /.nogai)
- ($.definition /.old_norse)
- ($.definition /.norwegian)
- ($.definition /.n'ko)
- ($.definition /.northern_sotho)
- ($.definition /.pedi)
- ($.definition /.sepedi)
- ($.definition /.nubian)
- ($.definition /.old_newari)
- ($.definition /.classical_newari)
- ($.definition /.classical_nepal_bhasa)
- ($.definition /.nyanja)
- ($.definition /.chichewa)
- ($.definition /.chewa)
- ($.definition /.nyamwezi)
- ($.definition /.nyankole)
- ($.definition /.nyoro)
- ($.definition /.nzima))))
+ (List $.Documentation)
+ (list ($.definition /.nahuatl)
+ ($.definition /.north_american_indian)
+ ($.definition /.neapolitan)
+ ($.definition /.nauru)
+ ($.definition /.navajo)
+ ($.definition /.south_ndebele)
+ ($.definition /.north_ndebele)
+ ($.definition /.ndonga)
+ ($.definition /.low_german)
+ ($.definition /.nepali)
+ ($.definition /.newari)
+ ($.definition /.nepal_bhasa)
+ ($.definition /.nias)
+ ($.definition /.niger_kordofanian)
+ ($.definition /.niuean)
+ ($.definition /.dutch)
+ ($.definition /.flemish)
+ ($.definition /.nynorsk)
+ ($.definition /.bokmal)
+ ($.definition /.nogai)
+ ($.definition /.old_norse)
+ ($.definition /.norwegian)
+ ($.definition /.n'ko)
+ ($.definition /.northern_sotho)
+ ($.definition /.pedi)
+ ($.definition /.sepedi)
+ ($.definition /.nubian)
+ ($.definition /.old_newari)
+ ($.definition /.classical_newari)
+ ($.definition /.classical_nepal_bhasa)
+ ($.definition /.nyanja)
+ ($.definition /.chichewa)
+ ($.definition /.chewa)
+ ($.definition /.nyamwezi)
+ ($.definition /.nyankole)
+ ($.definition /.nyoro)
+ ($.definition /.nzima)))
(def items/o
- (list.together
- (list ($.definition /.occitan)
- ($.definition /.provencal)
- ($.definition /.ojibwa)
- ($.definition /.oriya)
- ($.definition /.oromo)
- ($.definition /.osage)
- ($.definition /.ossetic)
- ($.definition /.ottoman_turkish)
- ($.definition /.otomian))))
+ (List $.Documentation)
+ (list ($.definition /.occitan)
+ ($.definition /.provencal)
+ ($.definition /.ojibwa)
+ ($.definition /.oriya)
+ ($.definition /.oromo)
+ ($.definition /.osage)
+ ($.definition /.ossetic)
+ ($.definition /.ottoman_turkish)
+ ($.definition /.otomian)))
(def items/p
- (list.together
- (list ($.definition /.papuan)
- ($.definition /.pangasinan)
- ($.definition /.pahlavi)
- ($.definition /.pampanga)
- ($.definition /.kapampangan)
- ($.definition /.punjabi)
- ($.definition /.papiamento)
- ($.definition /.palauan)
- ($.definition /.old_persian)
- ($.definition /.philippine)
- ($.definition /.phoenician)
- ($.definition /.pali)
- ($.definition /.polish)
- ($.definition /.pohnpeian)
- ($.definition /.portuguese)
- ($.definition /.prakrit)
- ($.definition /.old_provencal)
- ($.definition /.pashto))))
+ (List $.Documentation)
+ (list ($.definition /.papuan)
+ ($.definition /.pangasinan)
+ ($.definition /.pahlavi)
+ ($.definition /.pampanga)
+ ($.definition /.kapampangan)
+ ($.definition /.punjabi)
+ ($.definition /.papiamento)
+ ($.definition /.palauan)
+ ($.definition /.old_persian)
+ ($.definition /.philippine)
+ ($.definition /.phoenician)
+ ($.definition /.pali)
+ ($.definition /.polish)
+ ($.definition /.pohnpeian)
+ ($.definition /.portuguese)
+ ($.definition /.prakrit)
+ ($.definition /.old_provencal)
+ ($.definition /.pashto)))
(def items/q
- (list.together
- (list ($.definition /.quechua))))
+ (List $.Documentation)
+ (list ($.definition /.quechua)))
(def items/r
- (list.together
- (list ($.definition /.rajasthani)
- ($.definition /.rapanui)
- ($.definition /.rarotongan)
- ($.definition /.cook_islands_maori)
- ($.definition /.romance)
- ($.definition /.romansh)
- ($.definition /.romany)
- ($.definition /.romanian)
- ($.definition /.moldavian)
- ($.definition /.moldovan)
- ($.definition /.rundi)
- ($.definition /.aromanian)
- ($.definition /.arumanian)
- ($.definition /.macedo_romanian)
- ($.definition /.russian))))
+ (List $.Documentation)
+ (list ($.definition /.rajasthani)
+ ($.definition /.rapanui)
+ ($.definition /.rarotongan)
+ ($.definition /.cook_islands_maori)
+ ($.definition /.romance)
+ ($.definition /.romansh)
+ ($.definition /.romany)
+ ($.definition /.romanian)
+ ($.definition /.moldavian)
+ ($.definition /.moldovan)
+ ($.definition /.rundi)
+ ($.definition /.aromanian)
+ ($.definition /.arumanian)
+ ($.definition /.macedo_romanian)
+ ($.definition /.russian)))
(def items/s
- (list.together
- (list ($.definition /.sandawe)
- ($.definition /.sango)
- ($.definition /.yakut)
- ($.definition /.south_american_indian)
- ($.definition /.salishan)
- ($.definition /.samaritan_aramaic)
- ($.definition /.sanskrit)
- ($.definition /.sasak)
- ($.definition /.santali)
- ($.definition /.sicilian)
- ($.definition /.scots)
- ($.definition /.selkup)
- ($.definition /.semitic)
- ($.definition /.old_irish)
- ($.definition /.sign)
- ($.definition /.shan)
- ($.definition /.sidamo)
- ($.definition /.sinhalese)
- ($.definition /.siouan)
- ($.definition /.sino_tibetan)
- ($.definition /.slavic)
- ($.definition /.slovak)
- ($.definition /.slovenian)
- ($.definition /.southern_sami)
- ($.definition /.northern_sami)
- ($.definition /.sami)
- ($.definition /.lule)
- ($.definition /.inari)
- ($.definition /.samoan)
- ($.definition /.skolt_sami)
- ($.definition /.shona)
- ($.definition /.sindhi)
- ($.definition /.soninke)
- ($.definition /.sogdian)
- ($.definition /.somali)
- ($.definition /.songhai)
- ($.definition /.southern_sotho)
- ($.definition /.spanish)
- ($.definition /.castilian)
- ($.definition /.albanian)
- ($.definition /.sardinian)
- ($.definition /.sranan_tongo)
- ($.definition /.serbian)
- ($.definition /.serer)
- ($.definition /.nilo_saharan)
- ($.definition /.swati)
- ($.definition /.sukuma)
- ($.definition /.sundanese)
- ($.definition /.susu)
- ($.definition /.sumerian)
- ($.definition /.swahili)
- ($.definition /.swedish)
- ($.definition /.classical_syriac)
- ($.definition /.syriac))))
+ (List $.Documentation)
+ (list ($.definition /.sandawe)
+ ($.definition /.sango)
+ ($.definition /.yakut)
+ ($.definition /.south_american_indian)
+ ($.definition /.salishan)
+ ($.definition /.samaritan_aramaic)
+ ($.definition /.sanskrit)
+ ($.definition /.sasak)
+ ($.definition /.santali)
+ ($.definition /.sicilian)
+ ($.definition /.scots)
+ ($.definition /.selkup)
+ ($.definition /.semitic)
+ ($.definition /.old_irish)
+ ($.definition /.sign)
+ ($.definition /.shan)
+ ($.definition /.sidamo)
+ ($.definition /.sinhalese)
+ ($.definition /.siouan)
+ ($.definition /.sino_tibetan)
+ ($.definition /.slavic)
+ ($.definition /.slovak)
+ ($.definition /.slovenian)
+ ($.definition /.southern_sami)
+ ($.definition /.northern_sami)
+ ($.definition /.sami)
+ ($.definition /.lule)
+ ($.definition /.inari)
+ ($.definition /.samoan)
+ ($.definition /.skolt_sami)
+ ($.definition /.shona)
+ ($.definition /.sindhi)
+ ($.definition /.soninke)
+ ($.definition /.sogdian)
+ ($.definition /.somali)
+ ($.definition /.songhai)
+ ($.definition /.southern_sotho)
+ ($.definition /.spanish)
+ ($.definition /.castilian)
+ ($.definition /.albanian)
+ ($.definition /.sardinian)
+ ($.definition /.sranan_tongo)
+ ($.definition /.serbian)
+ ($.definition /.serer)
+ ($.definition /.nilo_saharan)
+ ($.definition /.swati)
+ ($.definition /.sukuma)
+ ($.definition /.sundanese)
+ ($.definition /.susu)
+ ($.definition /.sumerian)
+ ($.definition /.swahili)
+ ($.definition /.swedish)
+ ($.definition /.classical_syriac)
+ ($.definition /.syriac)))
(def items/t
- (list.together
- (list ($.definition /.tahitian)
- ($.definition /.tai)
- ($.definition /.tamil)
- ($.definition /.tatar)
- ($.definition /.telugu)
- ($.definition /.timne)
- ($.definition /.tereno)
- ($.definition /.tetum)
- ($.definition /.tajik)
- ($.definition /.tagalog)
- ($.definition /.thai)
- ($.definition /.tigre)
- ($.definition /.tigrinya)
- ($.definition /.tiv)
- ($.definition /.tokelau)
- ($.definition /.klingon)
- ($.definition /.tlingit)
- ($.definition /.tamashek)
- ($.definition /.tonga)
- ($.definition /.tongan)
- ($.definition /.tok_pisin)
- ($.definition /.tsimshian)
- ($.definition /.tswana)
- ($.definition /.tsonga)
- ($.definition /.turkmen)
- ($.definition /.tumbuka)
- ($.definition /.tupi)
- ($.definition /.turkish)
- ($.definition /.altaic)
- ($.definition /.tuvalu)
- ($.definition /.twi)
- ($.definition /.tuvinian))))
+ (List $.Documentation)
+ (list ($.definition /.tahitian)
+ ($.definition /.tai)
+ ($.definition /.tamil)
+ ($.definition /.tatar)
+ ($.definition /.telugu)
+ ($.definition /.timne)
+ ($.definition /.tereno)
+ ($.definition /.tetum)
+ ($.definition /.tajik)
+ ($.definition /.tagalog)
+ ($.definition /.thai)
+ ($.definition /.tigre)
+ ($.definition /.tigrinya)
+ ($.definition /.tiv)
+ ($.definition /.tokelau)
+ ($.definition /.klingon)
+ ($.definition /.tlingit)
+ ($.definition /.tamashek)
+ ($.definition /.tonga)
+ ($.definition /.tongan)
+ ($.definition /.tok_pisin)
+ ($.definition /.tsimshian)
+ ($.definition /.tswana)
+ ($.definition /.tsonga)
+ ($.definition /.turkmen)
+ ($.definition /.tumbuka)
+ ($.definition /.tupi)
+ ($.definition /.turkish)
+ ($.definition /.altaic)
+ ($.definition /.tuvalu)
+ ($.definition /.twi)
+ ($.definition /.tuvinian)))
(def items/u
- (list.together
- (list ($.definition /.udmurt)
- ($.definition /.ugaritic)
- ($.definition /.uyghur)
- ($.definition /.ukrainian)
- ($.definition /.umbundu)
- ($.definition /.urdu)
- ($.definition /.uzbek))))
+ (List $.Documentation)
+ (list ($.definition /.udmurt)
+ ($.definition /.ugaritic)
+ ($.definition /.uyghur)
+ ($.definition /.ukrainian)
+ ($.definition /.umbundu)
+ ($.definition /.urdu)
+ ($.definition /.uzbek)))
(def items/v
- (list.together
- (list ($.definition /.vai)
- ($.definition /.venda)
- ($.definition /.vietnamese)
- ($.definition /.volapük)
- ($.definition /.votic))))
+ (List $.Documentation)
+ (list ($.definition /.vai)
+ ($.definition /.venda)
+ ($.definition /.vietnamese)
+ ($.definition /.volapük)
+ ($.definition /.votic)))
(def items/w
- (list.together
- (list ($.definition /.wakashan)
- ($.definition /.walamo)
- ($.definition /.waray)
- ($.definition /.washo)
- ($.definition /.sorbian)
- ($.definition /.walloon)
- ($.definition /.wolof))))
+ (List $.Documentation)
+ (list ($.definition /.wakashan)
+ ($.definition /.walamo)
+ ($.definition /.waray)
+ ($.definition /.washo)
+ ($.definition /.sorbian)
+ ($.definition /.walloon)
+ ($.definition /.wolof)))
(def items/x
- (list.together
- (list ($.definition /.kalmyk)
- ($.definition /.oirat)
- ($.definition /.xhosa))))
+ (List $.Documentation)
+ (list ($.definition /.kalmyk)
+ ($.definition /.oirat)
+ ($.definition /.xhosa)))
(def items/y
- (list.together
- (list ($.definition /.yao)
- ($.definition /.yapese)
- ($.definition /.yiddish)
- ($.definition /.yoruba)
- ($.definition /.yupik))))
+ (List $.Documentation)
+ (list ($.definition /.yao)
+ ($.definition /.yapese)
+ ($.definition /.yiddish)
+ ($.definition /.yoruba)
+ ($.definition /.yupik)))
(def items/z
- (list.together
- (list ($.definition /.zapotec)
- ($.definition /.blissymbols)
- ($.definition /.zenaga)
- ($.definition /.standard_moroccan_tamazight)
- ($.definition /.zhuang)
- ($.definition /.chinese)
- ($.definition /.zande)
- ($.definition /.zulu)
- ($.definition /.zuni)
- ($.definition /.zaza)
- ($.definition /.dimili)
- ($.definition /.dimli)
- ($.definition /.kirdki)
- ($.definition /.kirmanjki)
- ($.definition /.zazaki))))
+ (List $.Documentation)
+ (list ($.definition /.zapotec)
+ ($.definition /.blissymbols)
+ ($.definition /.zenaga)
+ ($.definition /.standard_moroccan_tamazight)
+ ($.definition /.zhuang)
+ ($.definition /.chinese)
+ ($.definition /.zande)
+ ($.definition /.zulu)
+ ($.definition /.zuni)
+ ($.definition /.zaza)
+ ($.definition /.dimili)
+ ($.definition /.dimli)
+ ($.definition /.kirdki)
+ ($.definition /.kirmanjki)
+ ($.definition /.zazaki)))
-(.def .public documentation
- (.List $.Module)
- (`` ($.module /._
- ""
- [($.definition /.name)
- ($.definition /.code)
- ($.definition /.equivalence)
- ($.definition /.hash)
- ..items/~
- ..items/a
- ..items/b
- ..items/c
- ..items/d
- ..items/e
- ..items/f
- ..items/g
- ..items/h
- ..items/i
- ..items/j
- ..items/k
- ..items/l
- ..items/m
- ..items/n
- ..items/o
- ..items/p
- ..items/q
- ..items/r
- ..items/s
- ..items/t
- ..items/u
- ..items/v
- ..items/w
- ..items/x
- ..items/y
- ..items/z
+(def .public documentation
+ (List $.Documentation)
+ (`` (list.partial ($.module /._
+ "")
- ($.definition /.Language
- "An ISO 639 language.")]
- [])))
+ ($.definition /.name)
+ ($.definition /.code)
+ ($.definition /.equivalence)
+ ($.definition /.hash)
+
+ ($.definition /.Language
+ "An ISO 639 language.")
+
+ (all list#composite
+ ..items/~
+ ..items/a
+ ..items/b
+ ..items/c
+ ..items/d
+ ..items/e
+ ..items/f
+ ..items/g
+ ..items/h
+ ..items/i
+ ..items/j
+ ..items/k
+ ..items/l
+ ..items/m
+ ..items/n
+ ..items/o
+ ..items/p
+ ..items/q
+ ..items/r
+ ..items/s
+ ..items/t
+ ..items/u
+ ..items/v
+ ..items/w
+ ..items/x
+ ..items/y
+ ..items/z
+ )
+ )))
diff --git a/stdlib/source/documentation/lux/world/locale/territory.lux b/stdlib/source/documentation/lux/world/locale/territory.lux
index 6a54c5a00..7fff4eb60 100644
--- a/stdlib/source/documentation/lux/world/locale/territory.lux
+++ b/stdlib/source/documentation/lux/world/locale/territory.lux
@@ -6,315 +6,318 @@
[text
["%" \\format (.only format)]]
[collection
- ["[0]" list]]]]]
+ ["[0]" list (.use "[1]#[0]" monoid)]]]]]
[\\library
["[0]" /]])
(def items/ab
- (list.together
- (list ($.definition /.afghanistan)
- ($.definition /.aland_islands)
- ($.definition /.albania)
- ($.definition /.algeria)
- ($.definition /.american_samoa)
- ($.definition /.andorra)
- ($.definition /.angola)
- ($.definition /.anguilla)
- ($.definition /.antarctica)
- ($.definition /.antigua)
- ($.definition /.barbuda)
- ($.definition /.argentina)
- ($.definition /.armenia)
- ($.definition /.aruba)
- ($.definition /.australia)
- ($.definition /.austria)
- ($.definition /.azerbaijan)
- ($.definition /.the_bahamas)
- ($.definition /.bahrain)
- ($.definition /.bangladesh)
- ($.definition /.barbados)
- ($.definition /.belarus)
- ($.definition /.belgium)
- ($.definition /.belize)
- ($.definition /.benin)
- ($.definition /.bermuda)
- ($.definition /.bhutan)
- ($.definition /.bolivia)
- ($.definition /.bonaire)
- ($.definition /.sint_eustatius)
- ($.definition /.saba)
- ($.definition /.bosnia)
- ($.definition /.herzegovina)
- ($.definition /.botswana)
- ($.definition /.bouvet_island)
- ($.definition /.brazil)
- ($.definition /.british_indian_ocean_territory)
- ($.definition /.brunei_darussalam)
- ($.definition /.bulgaria)
- ($.definition /.burkina_faso)
- ($.definition /.burundi))))
+ (List $.Documentation)
+ (list ($.definition /.afghanistan)
+ ($.definition /.aland_islands)
+ ($.definition /.albania)
+ ($.definition /.algeria)
+ ($.definition /.american_samoa)
+ ($.definition /.andorra)
+ ($.definition /.angola)
+ ($.definition /.anguilla)
+ ($.definition /.antarctica)
+ ($.definition /.antigua)
+ ($.definition /.barbuda)
+ ($.definition /.argentina)
+ ($.definition /.armenia)
+ ($.definition /.aruba)
+ ($.definition /.australia)
+ ($.definition /.austria)
+ ($.definition /.azerbaijan)
+ ($.definition /.the_bahamas)
+ ($.definition /.bahrain)
+ ($.definition /.bangladesh)
+ ($.definition /.barbados)
+ ($.definition /.belarus)
+ ($.definition /.belgium)
+ ($.definition /.belize)
+ ($.definition /.benin)
+ ($.definition /.bermuda)
+ ($.definition /.bhutan)
+ ($.definition /.bolivia)
+ ($.definition /.bonaire)
+ ($.definition /.sint_eustatius)
+ ($.definition /.saba)
+ ($.definition /.bosnia)
+ ($.definition /.herzegovina)
+ ($.definition /.botswana)
+ ($.definition /.bouvet_island)
+ ($.definition /.brazil)
+ ($.definition /.british_indian_ocean_territory)
+ ($.definition /.brunei_darussalam)
+ ($.definition /.bulgaria)
+ ($.definition /.burkina_faso)
+ ($.definition /.burundi)))
(def items/cd
- (list.together
- (list ($.definition /.cape_verde)
- ($.definition /.cambodia)
- ($.definition /.cameroon)
- ($.definition /.canada)
- ($.definition /.cayman_islands)
- ($.definition /.central_african_republic)
- ($.definition /.chad)
- ($.definition /.chile)
- ($.definition /.china)
- ($.definition /.christmas_island)
- ($.definition /.cocos_islands)
- ($.definition /.colombia)
- ($.definition /.comoros)
- ($.definition /.congo)
- ($.definition /.democratic_republic_of_the_congo)
- ($.definition /.cook_islands)
- ($.definition /.costa_rica)
- ($.definition /.ivory_coast)
- ($.definition /.croatia)
- ($.definition /.cuba)
- ($.definition /.curacao)
- ($.definition /.cyprus)
- ($.definition /.czech_republic)
- ($.definition /.denmark)
- ($.definition /.djibouti)
- ($.definition /.dominica)
- ($.definition /.dominican_republic))))
+ (List $.Documentation)
+ (list ($.definition /.cape_verde)
+ ($.definition /.cambodia)
+ ($.definition /.cameroon)
+ ($.definition /.canada)
+ ($.definition /.cayman_islands)
+ ($.definition /.central_african_republic)
+ ($.definition /.chad)
+ ($.definition /.chile)
+ ($.definition /.china)
+ ($.definition /.christmas_island)
+ ($.definition /.cocos_islands)
+ ($.definition /.colombia)
+ ($.definition /.comoros)
+ ($.definition /.congo)
+ ($.definition /.democratic_republic_of_the_congo)
+ ($.definition /.cook_islands)
+ ($.definition /.costa_rica)
+ ($.definition /.ivory_coast)
+ ($.definition /.croatia)
+ ($.definition /.cuba)
+ ($.definition /.curacao)
+ ($.definition /.cyprus)
+ ($.definition /.czech_republic)
+ ($.definition /.denmark)
+ ($.definition /.djibouti)
+ ($.definition /.dominica)
+ ($.definition /.dominican_republic)))
(def items/efg
- (list.together
- (list ($.definition /.ecuador)
- ($.definition /.egypt)
- ($.definition /.el_salvador)
- ($.definition /.equatorial_guinea)
- ($.definition /.eritrea)
- ($.definition /.estonia)
- ($.definition /.eswatini)
- ($.definition /.ethiopia)
- ($.definition /.falkland_islands)
- ($.definition /.faroe_islands)
- ($.definition /.fiji)
- ($.definition /.finland)
- ($.definition /.france)
- ($.definition /.french_guiana)
- ($.definition /.french_polynesia)
- ($.definition /.french_southern_territories)
- ($.definition /.gabon)
- ($.definition /.the_gambia)
- ($.definition /.georgia)
- ($.definition /.germany)
- ($.definition /.ghana)
- ($.definition /.gibraltar)
- ($.definition /.greece)
- ($.definition /.greenland)
- ($.definition /.grenada)
- ($.definition /.guadeloupe)
- ($.definition /.guam)
- ($.definition /.guatemala)
- ($.definition /.guernsey)
- ($.definition /.guinea)
- ($.definition /.guinea_bissau)
- ($.definition /.guyana))))
+ (List $.Documentation)
+ (list ($.definition /.ecuador)
+ ($.definition /.egypt)
+ ($.definition /.el_salvador)
+ ($.definition /.equatorial_guinea)
+ ($.definition /.eritrea)
+ ($.definition /.estonia)
+ ($.definition /.eswatini)
+ ($.definition /.ethiopia)
+ ($.definition /.falkland_islands)
+ ($.definition /.faroe_islands)
+ ($.definition /.fiji)
+ ($.definition /.finland)
+ ($.definition /.france)
+ ($.definition /.french_guiana)
+ ($.definition /.french_polynesia)
+ ($.definition /.french_southern_territories)
+ ($.definition /.gabon)
+ ($.definition /.the_gambia)
+ ($.definition /.georgia)
+ ($.definition /.germany)
+ ($.definition /.ghana)
+ ($.definition /.gibraltar)
+ ($.definition /.greece)
+ ($.definition /.greenland)
+ ($.definition /.grenada)
+ ($.definition /.guadeloupe)
+ ($.definition /.guam)
+ ($.definition /.guatemala)
+ ($.definition /.guernsey)
+ ($.definition /.guinea)
+ ($.definition /.guinea_bissau)
+ ($.definition /.guyana)))
(def items/hijkl
- (list.together
- (list ($.definition /.haiti)
- ($.definition /.heard_island)
- ($.definition /.mcdonald_islands)
- ($.definition /.vatican_city)
- ($.definition /.honduras)
- ($.definition /.hong_kong)
- ($.definition /.hungary)
- ($.definition /.iceland)
- ($.definition /.india)
- ($.definition /.indonesia)
- ($.definition /.iran)
- ($.definition /.iraq)
- ($.definition /.ireland)
- ($.definition /.isle_of_man)
- ($.definition /.israel)
- ($.definition /.italy)
- ($.definition /.jamaica)
- ($.definition /.japan)
- ($.definition /.jersey)
- ($.definition /.jordan)
- ($.definition /.kazakhstan)
- ($.definition /.kenya)
- ($.definition /.kiribati)
- ($.definition /.north_korea)
- ($.definition /.south_korea)
- ($.definition /.kuwait)
- ($.definition /.kyrgyzstan)
- ($.definition /.laos)
- ($.definition /.latvia)
- ($.definition /.lebanon)
- ($.definition /.lesotho)
- ($.definition /.liberia)
- ($.definition /.libya)
- ($.definition /.liechtenstein)
- ($.definition /.lithuania)
- ($.definition /.luxembourg))))
+ (List $.Documentation)
+ (list ($.definition /.haiti)
+ ($.definition /.heard_island)
+ ($.definition /.mcdonald_islands)
+ ($.definition /.vatican_city)
+ ($.definition /.honduras)
+ ($.definition /.hong_kong)
+ ($.definition /.hungary)
+ ($.definition /.iceland)
+ ($.definition /.india)
+ ($.definition /.indonesia)
+ ($.definition /.iran)
+ ($.definition /.iraq)
+ ($.definition /.ireland)
+ ($.definition /.isle_of_man)
+ ($.definition /.israel)
+ ($.definition /.italy)
+ ($.definition /.jamaica)
+ ($.definition /.japan)
+ ($.definition /.jersey)
+ ($.definition /.jordan)
+ ($.definition /.kazakhstan)
+ ($.definition /.kenya)
+ ($.definition /.kiribati)
+ ($.definition /.north_korea)
+ ($.definition /.south_korea)
+ ($.definition /.kuwait)
+ ($.definition /.kyrgyzstan)
+ ($.definition /.laos)
+ ($.definition /.latvia)
+ ($.definition /.lebanon)
+ ($.definition /.lesotho)
+ ($.definition /.liberia)
+ ($.definition /.libya)
+ ($.definition /.liechtenstein)
+ ($.definition /.lithuania)
+ ($.definition /.luxembourg)))
(def items/mno
- (list.together
- (list ($.definition /.macau)
- ($.definition /.macedonia)
- ($.definition /.madagascar)
- ($.definition /.malawi)
- ($.definition /.malaysia)
- ($.definition /.maldives)
- ($.definition /.mali)
- ($.definition /.malta)
- ($.definition /.marshall_islands)
- ($.definition /.martinique)
- ($.definition /.mauritania)
- ($.definition /.mauritius)
- ($.definition /.mayotte)
- ($.definition /.mexico)
- ($.definition /.micronesia)
- ($.definition /.moldova)
- ($.definition /.monaco)
- ($.definition /.mongolia)
- ($.definition /.montenegro)
- ($.definition /.montserrat)
- ($.definition /.morocco)
- ($.definition /.mozambique)
- ($.definition /.myanmar)
- ($.definition /.namibia)
- ($.definition /.nauru)
- ($.definition /.nepal)
- ($.definition /.netherlands)
- ($.definition /.new_caledonia)
- ($.definition /.new_zealand)
- ($.definition /.nicaragua)
- ($.definition /.niger)
- ($.definition /.nigeria)
- ($.definition /.niue)
- ($.definition /.norfolk_island)
- ($.definition /.northern_mariana_islands)
- ($.definition /.norway)
- ($.definition /.oman))))
+ (List $.Documentation)
+ (list ($.definition /.macau)
+ ($.definition /.macedonia)
+ ($.definition /.madagascar)
+ ($.definition /.malawi)
+ ($.definition /.malaysia)
+ ($.definition /.maldives)
+ ($.definition /.mali)
+ ($.definition /.malta)
+ ($.definition /.marshall_islands)
+ ($.definition /.martinique)
+ ($.definition /.mauritania)
+ ($.definition /.mauritius)
+ ($.definition /.mayotte)
+ ($.definition /.mexico)
+ ($.definition /.micronesia)
+ ($.definition /.moldova)
+ ($.definition /.monaco)
+ ($.definition /.mongolia)
+ ($.definition /.montenegro)
+ ($.definition /.montserrat)
+ ($.definition /.morocco)
+ ($.definition /.mozambique)
+ ($.definition /.myanmar)
+ ($.definition /.namibia)
+ ($.definition /.nauru)
+ ($.definition /.nepal)
+ ($.definition /.netherlands)
+ ($.definition /.new_caledonia)
+ ($.definition /.new_zealand)
+ ($.definition /.nicaragua)
+ ($.definition /.niger)
+ ($.definition /.nigeria)
+ ($.definition /.niue)
+ ($.definition /.norfolk_island)
+ ($.definition /.northern_mariana_islands)
+ ($.definition /.norway)
+ ($.definition /.oman)))
(def items/pqrs
- (list.together
- (list ($.definition /.pakistan)
- ($.definition /.palau)
- ($.definition /.palestine)
- ($.definition /.panama)
- ($.definition /.papua_new_guinea)
- ($.definition /.paraguay)
- ($.definition /.peru)
- ($.definition /.philippines)
- ($.definition /.pitcairn_islands)
- ($.definition /.poland)
- ($.definition /.portugal)
- ($.definition /.puerto_rico)
- ($.definition /.qatar)
- ($.definition /.reunion)
- ($.definition /.romania)
- ($.definition /.russia)
- ($.definition /.rwanda)
- ($.definition /.saint_barthelemy)
- ($.definition /.saint_helena)
- ($.definition /.ascension)
- ($.definition /.tristan_da_cunha)
- ($.definition /.saint_kitts)
- ($.definition /.nevis)
- ($.definition /.saint_lucia)
- ($.definition /.saint_martin)
- ($.definition /.saint_pierre)
- ($.definition /.miquelon)
- ($.definition /.saint_vincent)
- ($.definition /.the_grenadines)
- ($.definition /.samoa)
- ($.definition /.san_marino)
- ($.definition /.sao_tome)
- ($.definition /.principe)
- ($.definition /.saudi_arabia)
- ($.definition /.senegal)
- ($.definition /.serbia)
- ($.definition /.seychelles)
- ($.definition /.sierra_leone)
- ($.definition /.singapore)
- ($.definition /.sint_maarten)
- ($.definition /.slovakia)
- ($.definition /.slovenia)
- ($.definition /.solomon_islands)
- ($.definition /.somalia)
- ($.definition /.south_africa)
- ($.definition /.south_georgia)
- ($.definition /.south_sandwich_islands)
- ($.definition /.south_sudan)
- ($.definition /.spain)
- ($.definition /.sri_lanka)
- ($.definition /.sudan)
- ($.definition /.suriname)
- ($.definition /.svalbard)
- ($.definition /.jan_mayen)
- ($.definition /.sweden)
- ($.definition /.switzerland)
- ($.definition /.syria))))
+ (List $.Documentation)
+ (list ($.definition /.pakistan)
+ ($.definition /.palau)
+ ($.definition /.palestine)
+ ($.definition /.panama)
+ ($.definition /.papua_new_guinea)
+ ($.definition /.paraguay)
+ ($.definition /.peru)
+ ($.definition /.philippines)
+ ($.definition /.pitcairn_islands)
+ ($.definition /.poland)
+ ($.definition /.portugal)
+ ($.definition /.puerto_rico)
+ ($.definition /.qatar)
+ ($.definition /.reunion)
+ ($.definition /.romania)
+ ($.definition /.russia)
+ ($.definition /.rwanda)
+ ($.definition /.saint_barthelemy)
+ ($.definition /.saint_helena)
+ ($.definition /.ascension)
+ ($.definition /.tristan_da_cunha)
+ ($.definition /.saint_kitts)
+ ($.definition /.nevis)
+ ($.definition /.saint_lucia)
+ ($.definition /.saint_martin)
+ ($.definition /.saint_pierre)
+ ($.definition /.miquelon)
+ ($.definition /.saint_vincent)
+ ($.definition /.the_grenadines)
+ ($.definition /.samoa)
+ ($.definition /.san_marino)
+ ($.definition /.sao_tome)
+ ($.definition /.principe)
+ ($.definition /.saudi_arabia)
+ ($.definition /.senegal)
+ ($.definition /.serbia)
+ ($.definition /.seychelles)
+ ($.definition /.sierra_leone)
+ ($.definition /.singapore)
+ ($.definition /.sint_maarten)
+ ($.definition /.slovakia)
+ ($.definition /.slovenia)
+ ($.definition /.solomon_islands)
+ ($.definition /.somalia)
+ ($.definition /.south_africa)
+ ($.definition /.south_georgia)
+ ($.definition /.south_sandwich_islands)
+ ($.definition /.south_sudan)
+ ($.definition /.spain)
+ ($.definition /.sri_lanka)
+ ($.definition /.sudan)
+ ($.definition /.suriname)
+ ($.definition /.svalbard)
+ ($.definition /.jan_mayen)
+ ($.definition /.sweden)
+ ($.definition /.switzerland)
+ ($.definition /.syria)))
(def items/tuvwxyz
- (list.together
- (list ($.definition /.taiwan)
- ($.definition /.tajikistan)
- ($.definition /.tanzania)
- ($.definition /.thailand)
- ($.definition /.east_timor)
- ($.definition /.togo)
- ($.definition /.tokelau)
- ($.definition /.tonga)
- ($.definition /.trinidad)
- ($.definition /.tobago)
- ($.definition /.tunisia)
- ($.definition /.turkey)
- ($.definition /.turkmenistan)
- ($.definition /.turks)
- ($.definition /.caicos_islands)
- ($.definition /.tuvalu)
- ($.definition /.uganda)
- ($.definition /.ukraine)
- ($.definition /.united_arab_emirates)
- ($.definition /.united_kingdom)
- ($.definition /.northern_ireland)
- ($.definition /.united_states_of_america)
- ($.definition /.united_states_minor_outlying_islands)
- ($.definition /.uruguay)
- ($.definition /.uzbekistan)
- ($.definition /.vanuatu)
- ($.definition /.venezuela)
- ($.definition /.vietnam)
- ($.definition /.british_virgin_islands)
- ($.definition /.united_states_virgin_islands)
- ($.definition /.wallis)
- ($.definition /.futuna)
- ($.definition /.western_sahara)
- ($.definition /.yemen)
- ($.definition /.zambia)
- ($.definition /.zimbabwe))))
+ (List $.Documentation)
+ (list ($.definition /.taiwan)
+ ($.definition /.tajikistan)
+ ($.definition /.tanzania)
+ ($.definition /.thailand)
+ ($.definition /.east_timor)
+ ($.definition /.togo)
+ ($.definition /.tokelau)
+ ($.definition /.tonga)
+ ($.definition /.trinidad)
+ ($.definition /.tobago)
+ ($.definition /.tunisia)
+ ($.definition /.turkey)
+ ($.definition /.turkmenistan)
+ ($.definition /.turks)
+ ($.definition /.caicos_islands)
+ ($.definition /.tuvalu)
+ ($.definition /.uganda)
+ ($.definition /.ukraine)
+ ($.definition /.united_arab_emirates)
+ ($.definition /.united_kingdom)
+ ($.definition /.northern_ireland)
+ ($.definition /.united_states_of_america)
+ ($.definition /.united_states_minor_outlying_islands)
+ ($.definition /.uruguay)
+ ($.definition /.uzbekistan)
+ ($.definition /.vanuatu)
+ ($.definition /.venezuela)
+ ($.definition /.vietnam)
+ ($.definition /.british_virgin_islands)
+ ($.definition /.united_states_virgin_islands)
+ ($.definition /.wallis)
+ ($.definition /.futuna)
+ ($.definition /.western_sahara)
+ ($.definition /.yemen)
+ ($.definition /.zambia)
+ ($.definition /.zimbabwe)))
-(.def .public documentation
- (.List $.Module)
- (`` ($.module /._
- ""
- [($.definition /.name)
- ($.definition /.short_code)
- ($.definition /.long_code)
- ($.definition /.numeric_code)
- ($.definition /.equivalence)
- ($.definition /.hash)
- ..items/ab
- ..items/cd
- ..items/efg
- ..items/hijkl
- ..items/mno
- ..items/pqrs
- ..items/tuvwxyz
+(def .public documentation
+ (List $.Documentation)
+ (`` (list.partial ($.module /._
+ "")
- ($.definition /.Territory
- "An ISO 3166 territory.")]
- [])))
+ ($.definition /.name)
+ ($.definition /.short_code)
+ ($.definition /.long_code)
+ ($.definition /.numeric_code)
+ ($.definition /.equivalence)
+ ($.definition /.hash)
+
+ ($.definition /.Territory
+ "An ISO 3166 territory.")
+
+ (all list#composite
+ ..items/ab
+ ..items/cd
+ ..items/efg
+ ..items/hijkl
+ ..items/mno
+ ..items/pqrs
+ ..items/tuvwxyz)
+ )))
diff --git a/stdlib/source/documentation/lux/world/net.lux b/stdlib/source/documentation/lux/world/net.lux
index 6ec146ddf..65d6c4316 100644
--- a/stdlib/source/documentation/lux/world/net.lux
+++ b/stdlib/source/documentation/lux/world/net.lux
@@ -4,7 +4,10 @@
["$" documentation]
["[0]" debug]
[control
- ["[0]" io]]]]
+ ["[0]" io]]
+ [data
+ [collection
+ ["[0]" list (.use "[1]#[0]" monoid)]]]]]
[\\library
["[0]" /]]
["[0]" /
@@ -13,20 +16,24 @@
["[1]/[0]" client]
["[1]/[0]" status]]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.Location)
+(def .public documentation
+ (List $.Documentation)
+ (list.partial ($.module /._
+ "")
- ($.definition /.Address
- "A TCP/IP address.")
+ ($.definition /.Location)
- ($.definition /.Port
- "A TCP/IP port.")
+ ($.definition /.Address
+ "A TCP/IP address.")
- ($.definition /.URL
- "A Uniform Resource Locator.")]
- [/uri.documentation
- /http/client.documentation
- /http/status.documentation]))
+ ($.definition /.Port
+ "A TCP/IP port.")
+
+ ($.definition /.URL
+ "A Uniform Resource Locator.")
+
+ (all list#composite
+ /uri.documentation
+ /http/client.documentation
+ /http/status.documentation)
+ ))
diff --git a/stdlib/source/documentation/lux/world/net/http/client.lux b/stdlib/source/documentation/lux/world/net/http/client.lux
index e306658a4..0330e372e 100644
--- a/stdlib/source/documentation/lux/world/net/http/client.lux
+++ b/stdlib/source/documentation/lux/world/net/http/client.lux
@@ -12,30 +12,31 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- (`` (`` ($.module /._
- ""
- [($.definition /.async)
- ($.definition /.headers)
- (,, (for @.jvm (,, (these ($.definition /.default)))
- (,, (these))))
+(def .public documentation
+ (List $.Documentation)
+ (`` (`` (list ($.module /._
+ "")
- ($.definition (/.Client !)
- "A HTTP client capable of issuing requests to a HTTP server.")
-
- (,, (with_template [<name>]
- [($.definition <name>
- (format "A " (text.upper_cased (template.text [<name>])) " request."))]
+ ($.definition /.async)
+ ($.definition /.headers)
+ (,, (for @.jvm (,, (these ($.definition /.default)))
+ (,, (these))))
- [/.post]
- [/.get]
- [/.put]
- [/.patch]
- [/.delete]
- [/.head]
- [/.connect]
- [/.options]
- [/.trace]
- ))]
- []))))
+ ($.definition (/.Client !)
+ "A HTTP client capable of issuing requests to a HTTP server.")
+
+ (,, (with_template [<name>]
+ [($.definition <name>
+ (format "A " (text.upper_cased (template.text [<name>])) " request."))]
+
+ [/.post]
+ [/.get]
+ [/.put]
+ [/.patch]
+ [/.delete]
+ [/.head]
+ [/.connect]
+ [/.options]
+ [/.trace]
+ ))
+ ))))
diff --git a/stdlib/source/documentation/lux/world/net/http/status.lux b/stdlib/source/documentation/lux/world/net/http/status.lux
index 94b646d02..0a65db6dd 100644
--- a/stdlib/source/documentation/lux/world/net/http/status.lux
+++ b/stdlib/source/documentation/lux/world/net/http/status.lux
@@ -11,87 +11,88 @@
[\\library
["[0]" /]])
-(`` (.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [(,, (with_template [<name>]
- [($.definition <name>
- (|> (template.text [<name>])
- (text.replaced "_" " ")
- text.upper_cased
- (format (%.nat <name>) ": ")))]
+(`` (def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ... 1xx Informational response
- [/.continue]
- [/.switching_protocols]
- [/.processing]
- [/.early_hints]
+ (,, (with_template [<name>]
+ [($.definition <name>
+ (|> (template.text [<name>])
+ (text.replaced "_" " ")
+ text.upper_cased
+ (format (%.nat <name>) ": ")))]
- ... 2xx Success
- [/.ok]
- [/.created]
- [/.accepted]
- [/.non_authoritative_information]
- [/.no_content]
- [/.reset_content]
- [/.partial_content]
- [/.multi_status]
- [/.already_reported]
- [/.im_used]
+ ... 1xx Informational response
+ [/.continue]
+ [/.switching_protocols]
+ [/.processing]
+ [/.early_hints]
- ... 3xx Redirection
- [/.multiple_choices]
- [/.moved_permanently]
- [/.found]
- [/.see_other]
- [/.not_modified]
- [/.use_proxy]
- [/.switch_proxy]
- [/.temporary_redirect]
- [/.permanent_redirect]
+ ... 2xx Success
+ [/.ok]
+ [/.created]
+ [/.accepted]
+ [/.non_authoritative_information]
+ [/.no_content]
+ [/.reset_content]
+ [/.partial_content]
+ [/.multi_status]
+ [/.already_reported]
+ [/.im_used]
- ... 4xx Client errors
- [/.bad_request]
- [/.unauthorized]
- [/.payment_required]
- [/.forbidden]
- [/.not_found]
- [/.method_not_allowed]
- [/.not_acceptable]
- [/.proxy_authentication_required]
- [/.request_timeout]
- [/.conflict]
- [/.gone]
- [/.length_required]
- [/.precondition_failed]
- [/.payload_too_large]
- [/.uri_too_long]
- [/.unsupported_media_type]
- [/.range_not_satisfiable]
- [/.expectation_failed]
- [/.im_a_teapot]
- [/.misdirected_request]
- [/.unprocessable_entity]
- [/.locked]
- [/.failed_dependency]
- [/.upgrade_required]
- [/.precondition_required]
- [/.too_many_requests]
- [/.request_header_fields_too_large]
- [/.unavailable_for_legal_reasons]
+ ... 3xx Redirection
+ [/.multiple_choices]
+ [/.moved_permanently]
+ [/.found]
+ [/.see_other]
+ [/.not_modified]
+ [/.use_proxy]
+ [/.switch_proxy]
+ [/.temporary_redirect]
+ [/.permanent_redirect]
- ... 5xx Server errors
- [/.internal_server_error]
- [/.not_implemented]
- [/.bad_gateway]
- [/.service_unavailable]
- [/.gateway_timeout]
- [/.http_version_not_supported]
- [/.variant_also_negotiates]
- [/.insufficient_storage]
- [/.loop_detected]
- [/.not_extended]
- [/.network_authentication_required]
- ))]
- [])))
+ ... 4xx Client errors
+ [/.bad_request]
+ [/.unauthorized]
+ [/.payment_required]
+ [/.forbidden]
+ [/.not_found]
+ [/.method_not_allowed]
+ [/.not_acceptable]
+ [/.proxy_authentication_required]
+ [/.request_timeout]
+ [/.conflict]
+ [/.gone]
+ [/.length_required]
+ [/.precondition_failed]
+ [/.payload_too_large]
+ [/.uri_too_long]
+ [/.unsupported_media_type]
+ [/.range_not_satisfiable]
+ [/.expectation_failed]
+ [/.im_a_teapot]
+ [/.misdirected_request]
+ [/.unprocessable_entity]
+ [/.locked]
+ [/.failed_dependency]
+ [/.upgrade_required]
+ [/.precondition_required]
+ [/.too_many_requests]
+ [/.request_header_fields_too_large]
+ [/.unavailable_for_legal_reasons]
+
+ ... 5xx Server errors
+ [/.internal_server_error]
+ [/.not_implemented]
+ [/.bad_gateway]
+ [/.service_unavailable]
+ [/.gateway_timeout]
+ [/.http_version_not_supported]
+ [/.variant_also_negotiates]
+ [/.insufficient_storage]
+ [/.loop_detected]
+ [/.not_extended]
+ [/.network_authentication_required]
+ ))
+ )))
diff --git a/stdlib/source/documentation/lux/world/net/uri.lux b/stdlib/source/documentation/lux/world/net/uri.lux
index 525dacf19..a3cd0ecac 100644
--- a/stdlib/source/documentation/lux/world/net/uri.lux
+++ b/stdlib/source/documentation/lux/world/net/uri.lux
@@ -8,13 +8,14 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.URI
- "A Uniform Resource Identifier.")
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.URI
+ "A Uniform Resource Identifier.")
- ($.definition /.separator
- "A separator for the pieces of a URI.")]
- []))
+ ($.definition /.separator
+ "A separator for the pieces of a URI.")
+ ))
diff --git a/stdlib/source/documentation/lux/world/output/video/resolution.lux b/stdlib/source/documentation/lux/world/output/video/resolution.lux
index 3ad820414..3595c1624 100644
--- a/stdlib/source/documentation/lux/world/output/video/resolution.lux
+++ b/stdlib/source/documentation/lux/world/output/video/resolution.lux
@@ -11,40 +11,41 @@
[\\library
["[0]" /]])
-(`` (.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.hash)
- ($.definition /.equivalence)
+(`` (def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition /.Resolution
- "A screen resolution.")
+ ($.definition /.hash)
+ ($.definition /.equivalence)
- (,, (with_template [<name>]
- [($.definition <name>
- (let [name (|> (template.text [<name>])
- (text.replaced "_" " ")
- text.upper_cased)]
- (format name " resolution: "
- (%.nat (the /.#width <name>))
- "x" (%.nat (the /.#height <name>))
- ".")))]
+ ($.definition /.Resolution
+ "A screen resolution.")
- [/.svga]
- [/.wsvga]
- [/.xga]
- [/.xga+]
- [/.wxga_16:9]
- [/.wxga_5:3]
- [/.wxga_16:10]
- [/.sxga]
- [/.wxga+]
- [/.hd+]
- [/.wsxga+]
- [/.fhd]
- [/.wuxga]
- [/.wqhd]
- [/.uhd_4k]
- ))]
- [])))
+ (,, (with_template [<name>]
+ [($.definition <name>
+ (let [name (|> (template.text [<name>])
+ (text.replaced "_" " ")
+ text.upper_cased)]
+ (format name " resolution: "
+ (%.nat (the /.#width <name>))
+ "x" (%.nat (the /.#height <name>))
+ ".")))]
+
+ [/.svga]
+ [/.wsvga]
+ [/.xga]
+ [/.xga+]
+ [/.wxga_16:9]
+ [/.wxga_5:3]
+ [/.wxga_16:10]
+ [/.sxga]
+ [/.wxga+]
+ [/.hd+]
+ [/.wsxga+]
+ [/.fhd]
+ [/.wuxga]
+ [/.wqhd]
+ [/.uhd_4k]
+ ))
+ )))
diff --git a/stdlib/source/documentation/lux/world/shell.lux b/stdlib/source/documentation/lux/world/shell.lux
index 100a642e2..7be466440 100644
--- a/stdlib/source/documentation/lux/world/shell.lux
+++ b/stdlib/source/documentation/lux/world/shell.lux
@@ -10,36 +10,37 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- (`` (`` ($.module /._
- ""
- [($.definition /.normal)
- ($.definition /.error)
- ($.definition /.async)
- (,, (for @.jvm (,, (these ($.definition /.no_more_output)
- ($.definition /.default)))
- (,, (these))))
-
- ($.definition /.Exit
- "A program exit code.")
-
- ($.definition (/.Process !)
- "The means for communicating with a program/process being executed by the operating system.")
-
- ($.definition /.Command
- "A command that can be executed by the operating system.")
-
- ($.definition /.Argument
- "A parameter for a command.")
-
- ($.definition (/.Shell !)
- "The means for issuing commands to the operating system.")
-
- ($.definition (/.Mock s)
- "A simulated process.")
-
- ($.definition /.mock
- ""
- [(mock mock init)])]
- []))))
+(def .public documentation
+ (List $.Documentation)
+ (`` (`` (list ($.module /._
+ "")
+
+ ($.definition /.normal)
+ ($.definition /.error)
+ ($.definition /.async)
+ (,, (for @.jvm (,, (these ($.definition /.no_more_output)
+ ($.definition /.default)))
+ (,, (these))))
+
+ ($.definition /.Exit
+ "A program exit code.")
+
+ ($.definition (/.Process !)
+ "The means for communicating with a program/process being executed by the operating system.")
+
+ ($.definition /.Command
+ "A command that can be executed by the operating system.")
+
+ ($.definition /.Argument
+ "A parameter for a command.")
+
+ ($.definition (/.Shell !)
+ "The means for issuing commands to the operating system.")
+
+ ($.definition (/.Mock s)
+ "A simulated process.")
+
+ ($.definition /.mock
+ ""
+ [(mock mock init)])
+ ))))
diff --git a/stdlib/source/documentation/lux/world/time.lux b/stdlib/source/documentation/lux/world/time.lux
index cd799e437..de12b24a0 100644
--- a/stdlib/source/documentation/lux/world/time.lux
+++ b/stdlib/source/documentation/lux/world/time.lux
@@ -1,10 +1,12 @@
(.require
[library
- [lux (.except and)
+ [lux (.except)
["$" documentation]
[data
["[0]" text (.only \n)
- ["%" \\format (.only format)]]]]]
+ ["%" \\format (.only format)]]
+ [collection
+ ["[0]" list (.use "[1]#[0]" monoid)]]]]]
[\\library
["[0]" /]]
["[0]" /
@@ -15,57 +17,62 @@
["[1][0]" month]
["[1][0]" year]])
-(`` (.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.time_exceeds_a_day)
- ($.definition /.invalid_hour)
- ($.definition /.invalid_minute)
- ($.definition /.invalid_second)
- ($.definition /.millis)
- ($.definition /.equivalence)
- ($.definition /.order)
- ($.definition /.enum)
- ($.definition /.parser)
+(`` (def .public documentation
+ (List $.Documentation)
+ (list.partial ($.module /._
+ "")
- (,, (with_template [<name> <doc>]
- [($.definition <name>
- <doc>)]
+ ($.definition /.time_exceeds_a_day)
+ ($.definition /.invalid_hour)
+ ($.definition /.invalid_minute)
+ ($.definition /.invalid_second)
+ ($.definition /.millis)
+ ($.definition /.equivalence)
+ ($.definition /.order)
+ ($.definition /.enum)
+ ($.definition /.parser)
- [/.milli_seconds "Number of milli-seconds in a second."]
- [/.seconds "Number of seconds in a minute."]
- [/.minutes "Number of minutes in an hour."]
- [/.hours "Number of hours in an day."]
- ))
+ (,, (with_template [<name> <doc>]
+ [($.definition <name>
+ <doc>)]
- ($.definition /.Time
- "Time is defined as milliseconds since the start of the day (00:00:00.000).")
+ [/.milli_seconds "Number of milli-seconds in a second."]
+ [/.seconds "Number of seconds in a minute."]
+ [/.minutes "Number of minutes in an hour."]
+ [/.hours "Number of hours in an day."]
+ ))
- ($.definition /.midnight
- "The instant corresponding to the start of the day: 00:00:00.000")
+ ($.definition /.Time
+ "Time is defined as milliseconds since the start of the day (00:00:00.000).")
- ($.definition /.of_millis
- ""
- [(of_millis milli_seconds)])
+ ($.definition /.midnight
+ "The instant corresponding to the start of the day: 00:00:00.000")
- ($.definition /.Clock
- "A clock marking the specific hour, minute, second, and milli-second in a day.")
+ ($.definition /.of_millis
+ ""
+ [(of_millis milli_seconds)])
- ($.definition /.clock
- ""
- [(clock time)])
+ ($.definition /.Clock
+ "A clock marking the specific hour, minute, second, and milli-second in a day.")
- ($.definition /.time
- ""
- [(time clock)])
+ ($.definition /.clock
+ ""
+ [(clock time)])
- ($.definition /.codec
- (format "Based on ISO 8601."
- \n "For example: 21:14:51.827"))]
- [/date.documentation
- /day.documentation
- /duration.documentation
- /instant.documentation
- /month.documentation
- /year.documentation])))
+ ($.definition /.time
+ ""
+ [(time clock)])
+
+ ($.definition /.codec
+ (format "Based on ISO 8601."
+ \n "For example: 21:14:51.827"))
+
+ (all list#composite
+ /date.documentation
+ /day.documentation
+ /duration.documentation
+ /instant.documentation
+ /month.documentation
+ /year.documentation
+ )
+ )))
diff --git a/stdlib/source/documentation/lux/world/time/date.lux b/stdlib/source/documentation/lux/world/time/date.lux
index 6d5716f7f..af7765e36 100644
--- a/stdlib/source/documentation/lux/world/time/date.lux
+++ b/stdlib/source/documentation/lux/world/time/date.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except and)
+ [lux (.except)
["$" documentation]
[data
["[0]" text (.only \n)
@@ -8,31 +8,32 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.invalid_day)
- ($.definition /.epoch)
- ($.definition /.year)
- ($.definition /.month)
- ($.definition /.day_of_month)
- ($.definition /.equivalence)
- ($.definition /.order)
- ($.definition /.invalid_month)
- ($.definition /.parser)
- ($.definition /.days)
- ($.definition /.of_days)
- ($.definition /.enum)
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition /.Date
- "A date specified as a year/month/day triplet.")
+ ($.definition /.invalid_day)
+ ($.definition /.epoch)
+ ($.definition /.year)
+ ($.definition /.month)
+ ($.definition /.day_of_month)
+ ($.definition /.equivalence)
+ ($.definition /.order)
+ ($.definition /.invalid_month)
+ ($.definition /.parser)
+ ($.definition /.days)
+ ($.definition /.of_days)
+ ($.definition /.enum)
- ($.definition /.date
- "A date, within the allowed limits."
- [(date year month day_of_month)])
+ ($.definition /.Date
+ "A date specified as a year/month/day triplet.")
- ($.definition /.codec
- (format "Based on ISO 8601."
- \n "For example: 2017-01-15"))]
- []))
+ ($.definition /.date
+ "A date, within the allowed limits."
+ [(date year month day_of_month)])
+
+ ($.definition /.codec
+ (format "Based on ISO 8601."
+ \n "For example: 2017-01-15"))
+ ))
diff --git a/stdlib/source/documentation/lux/world/time/day.lux b/stdlib/source/documentation/lux/world/time/day.lux
index d7441d2b7..8e55f69e2 100644
--- a/stdlib/source/documentation/lux/world/time/day.lux
+++ b/stdlib/source/documentation/lux/world/time/day.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except and)
+ [lux (.except)
["$" documentation]
[data
["[0]" text (.only \n)
@@ -8,23 +8,24 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.equivalence)
- ($.definition /.order)
- ($.definition /.enum)
- ($.definition /.not_a_day_of_the_week)
- ($.definition /.codec)
- ($.definition /.number)
- ($.definition /.invalid_day)
- ($.definition /.by_number)
- ($.definition /.hash)
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition /.Day
- "A day of the week.")
+ ($.definition /.equivalence)
+ ($.definition /.order)
+ ($.definition /.enum)
+ ($.definition /.not_a_day_of_the_week)
+ ($.definition /.codec)
+ ($.definition /.number)
+ ($.definition /.invalid_day)
+ ($.definition /.by_number)
+ ($.definition /.hash)
- ($.definition /.week
- "All the days, ordered by when they come in a week.")]
- []))
+ ($.definition /.Day
+ "A day of the week.")
+
+ ($.definition /.week
+ "All the days, ordered by when they come in a week.")
+ ))
diff --git a/stdlib/source/documentation/lux/world/time/duration.lux b/stdlib/source/documentation/lux/world/time/duration.lux
index f3725156c..a8dc682d2 100644
--- a/stdlib/source/documentation/lux/world/time/duration.lux
+++ b/stdlib/source/documentation/lux/world/time/duration.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except and)
+ [lux (.except)
["$" documentation]
[data
["[0]" text (.only \n)
@@ -8,40 +8,41 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.of_millis)
- ($.definition /.millis)
- ($.definition /.composite)
- ($.definition /.framed)
- ($.definition /.up)
- ($.definition /.down)
- ($.definition /.inverse)
- ($.definition /.ticks)
- ($.definition /.equivalence)
- ($.definition /.order)
- ($.definition /.positive?)
- ($.definition /.negative?)
- ($.definition /.neutral?)
- ($.definition /.empty)
- ($.definition /.milli_second)
- ($.definition /.second)
- ($.definition /.minute)
- ($.definition /.hour)
- ($.definition /.day)
- ($.definition /.week)
- ($.definition /.normal_year)
- ($.definition /.leap_year)
- ($.definition /.monoid)
- ($.definition /.codec)
- ($.definition /.enum)
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition /.Duration
- "Durations have a resolution of milli-seconds.")
+ ($.definition /.of_millis)
+ ($.definition /.millis)
+ ($.definition /.composite)
+ ($.definition /.framed)
+ ($.definition /.up)
+ ($.definition /.down)
+ ($.definition /.inverse)
+ ($.definition /.ticks)
+ ($.definition /.equivalence)
+ ($.definition /.order)
+ ($.definition /.positive?)
+ ($.definition /.negative?)
+ ($.definition /.neutral?)
+ ($.definition /.empty)
+ ($.definition /.milli_second)
+ ($.definition /.second)
+ ($.definition /.minute)
+ ($.definition /.hour)
+ ($.definition /.day)
+ ($.definition /.week)
+ ($.definition /.normal_year)
+ ($.definition /.leap_year)
+ ($.definition /.monoid)
+ ($.definition /.codec)
+ ($.definition /.enum)
- ($.definition /.difference
- ""
- [(difference from to)])]
- []))
+ ($.definition /.Duration
+ "Durations have a resolution of milli-seconds.")
+
+ ($.definition /.difference
+ ""
+ [(difference from to)])
+ ))
diff --git a/stdlib/source/documentation/lux/world/time/instant.lux b/stdlib/source/documentation/lux/world/time/instant.lux
index ae5ffb421..71efafd6c 100644
--- a/stdlib/source/documentation/lux/world/time/instant.lux
+++ b/stdlib/source/documentation/lux/world/time/instant.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except and)
+ [lux (.except)
["$" documentation]
[data
["[0]" text (.only \n)
@@ -8,49 +8,50 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.of_millis)
- ($.definition /.millis)
- ($.definition /.equivalence)
- ($.definition /.order)
- ($.definition /.enum)
- ($.definition /.date)
- ($.definition /.time)
- ($.definition /.day_of_week)
-
- ($.definition /.Instant
- "Instant is defined as milli-seconds since the epoch.")
-
- ($.definition /.span
- ""
- [(span from to)])
-
- ($.definition /.after
- ""
- [(after duration instant)])
-
- ($.definition /.relative
- ""
- [(relative instant)])
-
- ($.definition /.absolute
- ""
- [(absolute offset)])
-
- ($.definition /.epoch
- "The instant corresponding to 1970-01-01T00:00:00Z.")
-
- ($.definition /.codec
- (format "Based on ISO 8601."
- \n "For example: 2017-01-15T21:14:51.827Z"))
-
- ($.definition /.now
- "Yields the current instant, as measured from the operating-system's clock.")
-
- ($.definition /.of_date_time
- ""
- [(of_date_time date time)])]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.of_millis)
+ ($.definition /.millis)
+ ($.definition /.equivalence)
+ ($.definition /.order)
+ ($.definition /.enum)
+ ($.definition /.date)
+ ($.definition /.time)
+ ($.definition /.day_of_week)
+
+ ($.definition /.Instant
+ "Instant is defined as milli-seconds since the epoch.")
+
+ ($.definition /.span
+ ""
+ [(span from to)])
+
+ ($.definition /.after
+ ""
+ [(after duration instant)])
+
+ ($.definition /.relative
+ ""
+ [(relative instant)])
+
+ ($.definition /.absolute
+ ""
+ [(absolute offset)])
+
+ ($.definition /.epoch
+ "The instant corresponding to 1970-01-01T00:00:00Z.")
+
+ ($.definition /.codec
+ (format "Based on ISO 8601."
+ \n "For example: 2017-01-15T21:14:51.827Z"))
+
+ ($.definition /.now
+ "Yields the current instant, as measured from the operating-system's clock.")
+
+ ($.definition /.of_date_time
+ ""
+ [(of_date_time date time)])
+ ))
diff --git a/stdlib/source/documentation/lux/world/time/month.lux b/stdlib/source/documentation/lux/world/time/month.lux
index b1f03829c..60f1dcdea 100644
--- a/stdlib/source/documentation/lux/world/time/month.lux
+++ b/stdlib/source/documentation/lux/world/time/month.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except and)
+ [lux (.except)
["$" documentation]
[data
["[0]" text (.only \n)
@@ -8,31 +8,32 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.equivalence)
- ($.definition /.number)
- ($.definition /.invalid_month)
- ($.definition /.by_number)
- ($.definition /.hash)
- ($.definition /.order)
- ($.definition /.enum)
- ($.definition /.not_a_month_of_the_year)
- ($.definition /.codec)
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
- ($.definition /.Month
- "A month of the year.")
+ ($.definition /.equivalence)
+ ($.definition /.number)
+ ($.definition /.invalid_month)
+ ($.definition /.by_number)
+ ($.definition /.hash)
+ ($.definition /.order)
+ ($.definition /.enum)
+ ($.definition /.not_a_month_of_the_year)
+ ($.definition /.codec)
- ($.definition /.days
- "The amount of days of a month."
- [(days month)])
+ ($.definition /.Month
+ "A month of the year.")
- ($.definition /.leap_year_days
- "The amount of days of a month (in a leap year)."
- [(leap_year_days month)])
+ ($.definition /.days
+ "The amount of days of a month."
+ [(days month)])
- ($.definition /.year
- "All the months, ordered by when they come in a year.")]
- []))
+ ($.definition /.leap_year_days
+ "The amount of days of a month (in a leap year)."
+ [(leap_year_days month)])
+
+ ($.definition /.year
+ "All the months, ordered by when they come in a year.")
+ ))
diff --git a/stdlib/source/documentation/lux/world/time/year.lux b/stdlib/source/documentation/lux/world/time/year.lux
index 0f2a5825b..370c1cd2b 100644
--- a/stdlib/source/documentation/lux/world/time/year.lux
+++ b/stdlib/source/documentation/lux/world/time/year.lux
@@ -1,6 +1,6 @@
(.require
[library
- [lux (.except and)
+ [lux (.except)
["$" documentation]
[data
["[0]" text (.only \n)
@@ -8,41 +8,42 @@
[\\library
["[0]" /]])
-(.def .public documentation
- (.List $.Module)
- ($.module /._
- ""
- [($.definition /.there_is_no_year_0)
- ($.definition /.value)
- ($.definition /.epoch)
- ($.definition /.leap)
- ($.definition /.century)
- ($.definition /.era)
- ($.definition /.leap?)
- ($.definition /.parser)
- ($.definition /.equivalence)
- ($.definition /.order)
-
- ($.definition /.Year
- (format "A year in the gregorian calendar."
- \n "Both negative (< 0) and positive (> 0) values are valid, but not 0."
- \n "This is because the first year of the gregorian calendar was year 1."))
-
- ($.definition /.year
- "A valid year in the gregorian calendar, if possible."
- [(year value)])
-
- ($.definition /.days
- "The amount of days in a typical year.")
-
- ($.definition /.Period
- "An amount of years.")
-
- ($.definition /.leaps
- "The number of leap years in a period of years."
- [(leaps year)])
-
- ($.definition /.codec
- (format "Based on ISO 8601."
- \n "For example: 2017"))]
- []))
+(def .public documentation
+ (List $.Documentation)
+ (list ($.module /._
+ "")
+
+ ($.definition /.there_is_no_year_0)
+ ($.definition /.value)
+ ($.definition /.epoch)
+ ($.definition /.leap)
+ ($.definition /.century)
+ ($.definition /.era)
+ ($.definition /.leap?)
+ ($.definition /.parser)
+ ($.definition /.equivalence)
+ ($.definition /.order)
+
+ ($.definition /.Year
+ (format "A year in the gregorian calendar."
+ \n "Both negative (< 0) and positive (> 0) values are valid, but not 0."
+ \n "This is because the first year of the gregorian calendar was year 1."))
+
+ ($.definition /.year
+ "A valid year in the gregorian calendar, if possible."
+ [(year value)])
+
+ ($.definition /.days
+ "The amount of days in a typical year.")
+
+ ($.definition /.Period
+ "An amount of years.")
+
+ ($.definition /.leaps
+ "The number of leap years in a period of years."
+ [(leaps year)])
+
+ ($.definition /.codec
+ (format "Based on ISO 8601."
+ \n "For example: 2017"))
+ ))