aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux.lux
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux.lux905
1 files changed, 448 insertions, 457 deletions
diff --git a/stdlib/source/lux.lux b/stdlib/source/lux.lux
index bf92eb4db..916b77797 100644
--- a/stdlib/source/lux.lux
+++ b/stdlib/source/lux.lux
@@ -1,8 +1,17 @@
+("lux def" double-quote
+ ("lux int char" +34)
+ [["" 0 0] (10 (0))])
+
+("lux def" new-line
+ ("lux int char" +10)
+ [["" 0 0] (10 (0))])
+
+("lux def" __paragraph
+ ("lux text concat" new-line new-line)
+ [["" 0 0] (10 (0))])
+
("lux def" dummy-cursor
- ("lux check" (2 (0 "#Text" (0))
- (2 (0 "#I64" (1 (0 "#Nat" (0)) (0)))
- (0 "#I64" (1 (0 "#Nat" (0)) (0)))))
- ["" 0 0])
+ ["" 0 0]
[["" 0 0]
(10 (1 [[["" 0 0] (7 ["lux" "export?"])]
[["" 0 0] (0 #1)]]
@@ -19,9 +28,9 @@
(1 [[dummy-cursor (7 ["lux" "export?"])]
[dummy-cursor (0 #1)]]
(1 [[dummy-cursor (7 ["lux" "doc"])]
- [dummy-cursor (5 "The type of things whose type does not matter.
-
- It can be used to write functions or data-structures that can take, or return, anything.")]]
+ [dummy-cursor (5 ("lux text concat"
+ ("lux text concat" "The type of things whose type is irrelevant." __paragraph)
+ "It can be used to write functions or data-structures that can take, or return, anything."))]]
(0)))))])
## (type: Nothing
@@ -35,9 +44,9 @@
(1 [[dummy-cursor (7 ["lux" "export?"])]
[dummy-cursor (0 #1)]]
(1 [[dummy-cursor (7 ["lux" "doc"])]
- [dummy-cursor (5 "The type of things whose type is unknown or undefined.
-
- Useful for expressions that cause errors or other \"extraordinary\" conditions.")]]
+ [dummy-cursor (5 ("lux text concat"
+ ("lux text concat" "The type of things whose type is undefined." __paragraph)
+ "Useful for expressions that cause errors or other 'extraordinary' conditions."))]]
(0)))))])
## (type: (List a)
@@ -98,9 +107,9 @@
(#Cons [[dummy-cursor (7 ["lux" "export?"])]
[dummy-cursor (0 #1)]]
(#Cons [[dummy-cursor (7 ["lux" "doc"])]
- [dummy-cursor (5 "Natural numbers (unsigned integers).
-
- They start at zero (0) and extend in the positive direction.")]]
+ [dummy-cursor (5 ("lux text concat"
+ ("lux text concat" "Natural numbers (unsigned integers)." __paragraph)
+ "They start at zero (0) and extend in the positive direction."))]]
#Nil))))])
("lux def" Int
@@ -124,9 +133,9 @@
(#Cons [[dummy-cursor (7 ["lux" "export?"])]
[dummy-cursor (0 #1)]]
(#Cons [[dummy-cursor (7 ["lux" "doc"])]
- [dummy-cursor (5 "Fractional numbers that live in the interval [0,1).
-
- Useful for probability, and other domains that work within that interval.")]]
+ [dummy-cursor (5 ("lux text concat"
+ ("lux text concat" "Fractional numbers that live in the interval [0,1)." __paragraph)
+ "Useful for probability, and other domains that work within that interval."))]]
#Nil))))])
("lux def" Frac
@@ -162,9 +171,7 @@
(#Cons [[dummy-cursor (7 ["lux" "export?"])]
[dummy-cursor (0 #1)]]
(#Cons [[dummy-cursor (7 ["lux" "doc"])]
- [dummy-cursor (5 "A name.
-
- It is used as part of Lux syntax to represent identifiers and tags.")]]
+ [dummy-cursor (5 "A name. It is used as part of Lux syntax to represent identifiers and tags.")]]
#Nil))))])
## (type: (Maybe a)
@@ -747,11 +754,11 @@
(#Cons (text$ "host")
#Nil)))))))))))))]
(#Cons [(tag$ ["lux" "doc"])
- (text$ "Represents the state of the Lux compiler during a run.
-
- It is provided to macros during their invocation, so they can access compiler data.
-
- Caveat emptor: Avoid fiddling with it, unless you know what you're doing.")]
+ (text$ ("lux text concat"
+ ("lux text concat" "Represents the state of the Lux compiler during a run." __paragraph)
+ ("lux text concat"
+ ("lux text concat" "It is provided to macros during their invocation, so they can access compiler data." __paragraph)
+ "Caveat emptor: Avoid fiddling with it, unless you know what you're doing.")))]
default-def-meta-exported))))
## (type: (Meta a)
@@ -763,9 +770,9 @@
(#Apply (#Product Lux (#Parameter 1))
(#Apply Text Either)))))
(record$ (#Cons [(tag$ ["lux" "doc"])
- (text$ "Computations that can have access to the state of the compiler.
-
- These computations may fail, or modify the state of the compiler.")]
+ (text$ ("lux text concat"
+ ("lux text concat" "Computations that can have access to the state of the compiler." __paragraph)
+ "These computations may fail, or modify the state of the compiler."))]
(#Cons [(tag$ ["lux" "type-args"])
(tuple$ (#Cons (text$ "a") #Nil))]
default-def-meta-exported))))
@@ -1027,9 +1034,11 @@
(macro:' #export (comment tokens)
(#Cons [(tag$ ["lux" "doc"])
- (text$ "## Throws away any code given to it.
- ## Great for commenting-out code, while retaining syntax high-lighting and formatting in your text editor.
- (comment +1 +2 +3 +4)")]
+ (text$ ("lux text concat"
+ ("lux text concat" "## Throws away any code given to it." __paragraph)
+ ("lux text concat"
+ ("lux text concat" "## Great for commenting-out code, while retaining syntax high-lighting and formatting in your text editor." __paragraph)
+ "(comment +1 +2 +3 +4)")))]
#Nil)
(return #Nil))
@@ -1219,14 +1228,13 @@
(macro:' #export (All tokens)
(#Cons [(tag$ ["lux" "doc"])
- (text$ "## Universal quantification.
- (All [a]
- (-> a a))
-
- ## A name can be provided, to specify a recursive type.
- (All List [a]
- (| Any
- [a (List a)]))")]
+ (text$ ("lux text concat"
+ ("lux text concat" "## Universal quantification." __paragraph)
+ ("lux text concat"
+ ("lux text concat" "(All [a] (-> a a))" __paragraph)
+ ("lux text concat"
+ ("lux text concat" "## A name can be provided, to specify a recursive type." __paragraph)
+ "(All List [a] (| Any [a (List a)]))"))))]
#Nil)
(let'' [self-name tokens] ({(#Cons [_ (#Identifier "" self-name)] tokens)
[self-name tokens]
@@ -1264,16 +1272,13 @@
(macro:' #export (Ex tokens)
(#Cons [(tag$ ["lux" "doc"])
- (text$ "## 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))])")]
+ (text$ ("lux text concat"
+ ("lux text concat" "## Existential quantification." __paragraph)
+ ("lux text concat"
+ ("lux text concat" "(Ex [a] [(Codec Text a) a])" __paragraph)
+ ("lux text concat"
+ ("lux text concat" "## A name can be provided, to specify a recursive type." __paragraph)
+ "(Ex Self [a] [(Codec Text a) a (List (Self a))])"))))]
#Nil)
(let'' [self-name tokens] ({(#Cons [_ (#Identifier "" self-name)] tokens)
[self-name tokens]
@@ -1319,10 +1324,11 @@
(macro:' #export (-> tokens)
(#Cons [(tag$ ["lux" "doc"])
- (text$ "## Function types:
- (-> Int Int Int)
-
- ## This is the type of a function that takes 2 Ints and returns an Int.")]
+ (text$ ("lux text concat"
+ ("lux text concat" "## Function types:" __paragraph)
+ ("lux text concat"
+ ("lux text concat" "(-> Int Int Int)" __paragraph)
+ "## This is the type of a function that takes 2 Ints and returns an Int.")))]
#Nil)
({(#Cons output inputs)
(return (#Cons (list/fold ("lux check" (#Function Code (#Function Code Code))
@@ -1337,8 +1343,9 @@
(macro:' #export (list xs)
(#Cons [(tag$ ["lux" "doc"])
- (text$ "## List-construction macro.
- (list +1 +2 +3)")]
+ (text$ ("lux text concat"
+ ("lux text concat" "## List-construction macro." __paragraph)
+ "(list +1 +2 +3)"))]
#Nil)
(return (#Cons (list/fold (function'' [head tail]
(form$ (#Cons (tag$ ["lux" "Cons"])
@@ -1350,9 +1357,11 @@
(macro:' #export (list& xs)
(#Cons [(tag$ ["lux" "doc"])
- (text$ "## List-construction macro, with the last element being a tail-list.
- ## In other words, this macro prepends elements to another list.
- (list& +1 +2 +3 (list +4 +5 +6))")]
+ (text$ ("lux text concat"
+ ("lux text concat" "## List-construction macro, with the last element being a tail-list." __paragraph)
+ ("lux text concat"
+ ("lux text concat" "## In other words, this macro prepends elements to another list." __paragraph)
+ "(list& +1 +2 +3 (list +4 +5 +6))")))]
#Nil)
({(#Cons last init)
(return (list (list/fold (function'' [head tail]
@@ -1367,11 +1376,13 @@
(macro:' #export (& tokens)
(#Cons [(tag$ ["lux" "doc"])
- (text$ "## Tuple types:
- (& Text Int Bit)
-
- ## Any.
- (&)")]
+ (text$ ("lux text concat"
+ ("lux text concat" "## Tuple types:" __paragraph)
+ ("lux text concat"
+ ("lux text concat" "(& Text Int Bit)" __paragraph)
+ ("lux text concat"
+ ("lux text concat" "## Any." __paragraph)
+ "(&)"))))]
#Nil)
({#Nil
(return (list (identifier$ ["lux" "Any"])))
@@ -1384,11 +1395,13 @@
(macro:' #export (| tokens)
(#Cons [(tag$ ["lux" "doc"])
- (text$ "## Variant types:
- (| Text Int Bit)
-
- ## Nothing.
- (|)")]
+ (text$ ("lux text concat"
+ ("lux text concat" "## Variant types:" __paragraph)
+ ("lux text concat"
+ ("lux text concat" "(| Text Int Bit)" __paragraph)
+ ("lux text concat"
+ ("lux text concat" "## Nothing." __paragraph)
+ "(|)"))))]
#Nil)
({#Nil
(return (list (identifier$ ["lux" "Nothing"])))
@@ -1563,11 +1576,13 @@
(macro:' #export (_$ tokens)
(#Cons [(tag$ ["lux" "doc"])
- (text$ "## Left-association for the application of binary functions over variadic arguments.
- (_$ text/compose \"Hello, \" name \".\\nHow are you?\")
-
- ## =>
- (text/compose (text/compose \"Hello, \" name) \".\\nHow are you?\")")]
+ (text$ ("lux text concat"
+ ("lux text concat" "## Left-association for the application of binary functions over variadic arguments." ..new-line)
+ ("lux text concat"
+ ("lux text concat" "(_$ text/compose ''Hello, '' name ''. How are you?'')" ..new-line)
+ ("lux text concat"
+ ("lux text concat" "## =>" ..new-line)
+ "(text/compose (text/compose ''Hello, '' name) ''. How are you?'')"))))]
#Nil)
({(#Cons op tokens')
({(#Cons first nexts)
@@ -1583,11 +1598,13 @@
(macro:' #export ($_ tokens)
(#Cons [(tag$ ["lux" "doc"])
- (text$ "## Right-association for the application of binary functions over variadic arguments.
- ($_ text/compose \"Hello, \" name \".\\nHow are you?\")
-
- ## =>
- (text/compose \"Hello, \" (text/compose name \".\\nHow are you?\"))")]
+ (text$ ("lux text concat"
+ ("lux text concat" "## Right-association for the application of binary functions over variadic arguments." ..new-line)
+ ("lux text concat"
+ ("lux text concat" "($_ text/compose ''Hello, '' name ''. How are you?'')" ..new-line)
+ ("lux text concat"
+ ("lux text concat" "## =>" ..new-line)
+ "(text/compose ''Hello, '' (text/compose name ''. How are you?''))"))))]
#Nil)
({(#Cons op tokens')
({(#Cons last prevs)
@@ -1715,13 +1732,10 @@
(macro:' #export (if tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "Picks which expression to evaluate based on a bit test value.
-
- (if #1
- \"Oh, yeah!\"
- \"Aw hell naw!\")
-
- => \"Oh, yeah!\"")])
+ (text$ ($_ "lux text concat"
+ "Picks which expression to evaluate based on a bit test value." __paragraph
+ "(if #1 ''Oh, yeah!'' ''Aw hell naw!'')" __paragraph
+ "=> ''Oh, yeah!''"))])
({(#Cons test (#Cons then (#Cons else #Nil)))
(return (list (form$ (list (record$ (list [(bit$ #1) then]
[(bit$ #0) else]))
@@ -1759,9 +1773,9 @@
(def:''' #export (log! message)
(list [(tag$ ["lux" "doc"])
- (text$ "Logs message to standard output.
-
- Useful for debugging.")])
+ (text$ ($_ "lux text concat"
+ "Logs message to standard output." __paragraph
+ "Useful for debugging."))])
(-> Text Any)
("lux io log" message))
@@ -1966,10 +1980,10 @@
(macro:' #export (primitive tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "## Macro to treat define new primitive types.
- (primitive \"java.lang.Object\")
-
- (primitive \"java.util.List\" [(primitive \"java.lang.Long\")])")])
+ (text$ ($_ "lux text concat"
+ "## Macro to treat define new primitive types." __paragraph
+ "(primitive ''java.lang.Object'')" __paragraph
+ "(primitive ''java.util.List'' [(primitive ''java.lang.Long'')])"))])
({(#Cons [_ (#Text class-name)] #Nil)
(return (list (form$ (list (tag$ ["lux" "Primitive"]) (text$ class-name) (tag$ ["lux" "Nil"])))))
@@ -1997,11 +2011,10 @@
(macro:' #export (` tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "## Hygienic quasi-quotation as a macro. Unquote (~) and unquote-splice (~+) must also be used as forms.
- ## 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))))")])
+ (text$ ($_ "lux text concat"
+ "## Hygienic quasi-quotation as a macro. Unquote (~) and unquote-splice (~+) must also be used as forms." __paragraph
+ "## 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." __paragraph
+ "(` (def: (~ name) (function ((~' _) (~+ args)) (~ body))))"))])
({(#Cons template #Nil)
(do Monad<Meta>
[current-module current-module-name
@@ -2016,10 +2029,9 @@
(macro:' #export (`' tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "## Unhygienic quasi-quotation as a macro. Unquote (~) and unquote-splice (~+) must also be used as forms.
- (`' (def: (~ name)
- (function (_ (~+ args))
- (~ body))))")])
+ (text$ ($_ "lux text concat"
+ "## Unhygienic quasi-quotation as a macro. Unquote (~) and unquote-splice (~+) must also be used as forms." __paragraph
+ "(`' (def: (~ name) (function (_ (~+ args)) (~ body))))"))])
({(#Cons template #Nil)
(do Monad<Meta>
[=template (untemplate #1 "" template)]
@@ -2031,8 +2043,9 @@
(macro:' #export (' tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "## Quotation as a macro.
- (' \"YOLO\")")])
+ (text$ ($_ "lux text concat"
+ "## Quotation as a macro." __paragraph
+ "(' YOLO)"))])
({(#Cons template #Nil)
(do Monad<Meta>
[=template (untemplate #0 "" template)]
@@ -2044,13 +2057,11 @@
(macro:' #export (|> tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "## Piping macro.
- (|> elems (list/map int/encode) (interpose \" \") (fold text/compose \"\"))
-
- ## =>
- (fold text/compose \"\"
- (interpose \" \"
- (list/map int/encode elems)))")])
+ (text$ ($_ "lux text concat"
+ "## Piping macro." __paragraph
+ "(|> elems (list/map int/encode) (interpose '' '') (fold text/compose ''''))" __paragraph
+ "## =>" __paragraph
+ "(fold text/compose '''' (interpose '' '' (list/map int/encode elems)))"))])
({(#Cons [init apps])
(return (list (list/fold ("lux check" (-> Code Code Code)
(function' [app acc]
@@ -2072,13 +2083,11 @@
(macro:' #export (<| tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "## Reverse piping macro.
- (<| (fold text/compose \"\") (interpose \" \") (list/map int/encode) elems)
-
- ## =>
- (fold text/compose \"\"
- (interpose \" \"
- (list/map int/encode elems)))")])
+ (text$ ($_ "lux text concat"
+ "## Reverse piping macro." __paragraph
+ "(<| (fold text/compose '''') (interpose '' '') (list/map int/encode) elems)" __paragraph
+ "## =>" __paragraph
+ "(fold text/compose '''' (interpose '' '' (list/map int/encode elems)))"))])
({(#Cons [init apps])
(return (list (list/fold ("lux check" (-> Code Code Code)
(function' [app acc]
@@ -2249,14 +2258,12 @@
(macro:' #export (do-template tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "## By specifying a pattern (with holes), and the input data to fill those holes, repeats the pattern as many times as necessary.
- (do-template [<name> <diff>]
- [(def: #export <name>
- (-> Int Int)
- (i/+ <diff>))]
-
- [inc +1]
- [dec -1])")])
+ (text$ ($_ "lux text concat"
+ "## By specifying a pattern (with holes), and the input data to fill those holes, repeats the pattern as many times as necessary." __paragraph
+ "(do-template [<name> <diff>]" ..new-line
+ " " "[(def: #export <name> (-> Int Int) (i/+ <diff>))]" __paragraph
+ " " "[inc +1]" ..new-line
+ " " "[dec -1]"))])
({(#Cons [[_ (#Tuple bindings)] (#Cons [[_ (#Tuple templates)] data])])
({[(#Some bindings') (#Some data')]
(let' [apply ("lux check" (-> RepEnv ($' List Code))
@@ -2602,11 +2609,10 @@
(def:''' #export (not x)
(list [(tag$ ["lux" "doc"])
- (text$ "## Bit negation.
-
- (not #1) => #0
-
- (not #0) => #1")])
+ (text$ ($_ "lux text concat"
+ "## Bit negation." __paragraph
+ "(not #1) => #0" __paragraph
+ "(not #0) => #1"))])
(-> Bit Bit)
(if x #0 #1))
@@ -2815,8 +2821,9 @@
(macro:' #export (type tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "## Takes a type expression and returns it's representation as data-structure.
- (type (All [a] (Maybe (List a))))")])
+ (text$ ($_ "lux text concat"
+ "## Takes a type expression and returns it's representation as data-structure." __paragraph
+ "(type (All [a] (Maybe (List a))))"))])
({(#Cons type #Nil)
(do Monad<Meta>
[type+ (macro-expand-all type)]
@@ -2833,8 +2840,9 @@
(macro:' #export (: tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "## The type-annotation macro.
- (: (List Int) (list +1 +2 +3))")])
+ (text$ ($_ "lux text concat"
+ "## The type-annotation macro." __paragraph
+ "(: (List Int) (list +1 +2 +3))"))])
({(#Cons type (#Cons value #Nil))
(return (list (` ("lux check" (type (~ type)) (~ value)))))
@@ -2844,8 +2852,9 @@
(macro:' #export (:coerce tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "## The type-coercion macro.
- (:coerce Dinosaur (list +1 +2 +3))")])
+ (text$ ($_ "lux text concat"
+ "## The type-coercion macro." __paragraph
+ "(:coerce Dinosaur (list +1 +2 +3))"))])
({(#Cons type (#Cons value #Nil))
(return (list (` ("lux coerce" (type (~ type)) (~ value)))))
@@ -2941,10 +2950,10 @@
(macro:' #export (Rec tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "## Parameter-less recursive types.
- ## A name has to be given to the whole type, to use it within its body.
- (Rec Self
- [Int (List Self)])")])
+ (text$ ($_ "lux text concat"
+ "## Parameter-less recursive types." __paragraph
+ "## A name has to be given to the whole type, to use it within its body." __paragraph
+ "(Rec Self [Int (List Self)])"))])
({(#Cons [_ (#Identifier "" name)] (#Cons body #Nil))
(let' [body' (replace-syntax (list [name (` (#.Apply (~ (make-parameter 1)) (~ (make-parameter 0))))])
(update-parameters body))]
@@ -2956,12 +2965,13 @@
(macro:' #export (exec tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "## Sequential execution of expressions (great for side-effects).
- (exec
- (log! \"#1\")
- (log! \"#2\")
- (log! \"#3\")
- \"YOLO\")")])
+ (text$ ($_ "lux text concat"
+ "## Sequential execution of expressions (great for side-effects)." __paragraph
+ "(exec" ..new-line
+ " " "(log! ''#1'')" ..new-line
+ " " "(log! ''#2'')" ..new-line
+ " " "(log! ''#3'')" ..new-line
+ "''YOLO'')"))])
({(#Cons value actions)
(let' [dummy (identifier$ ["" ""])]
(return (list (list/fold ("lux check" (-> Code Code Code)
@@ -3043,7 +3053,7 @@
(frac/encode value)
[_ (#Text value)]
- ($_ text/compose "\"" value "\"")
+ ($_ text/compose ..double-quote value ..double-quote)
[_ (#Identifier [prefix name])]
(if (text/= "" prefix)
@@ -3104,23 +3114,23 @@
(do Monad<Meta> [] (wrap (list)))
_
- (fail ($_ text/compose "\"lux.case\" expects an even number of tokens: " (|> branches
- (list/map code-to-text)
- (interpose " ")
- list/reverse
- (list/fold text/compose ""))))}
+ (fail ($_ text/compose "'lux.case' expects an even number of tokens: " (|> branches
+ (list/map code-to-text)
+ (interpose " ")
+ list/reverse
+ (list/fold text/compose ""))))}
branches))
(macro:' #export (case tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "## The pattern-matching macro.
- ## Allows the usage of macros within the patterns to provide custom syntax.
- (case (: (List Int) (list +1 +2 +3))
- (#Cons x (#Cons y (#Cons z #Nil)))
- (#Some ($_ i/* x y z))
-
- _
- #None)")])
+ (text$ ($_ "lux text concat"
+ "## The pattern-matching macro." ..new-line
+ "## Allows the usage of macros within the patterns to provide custom syntax." ..new-line
+ "(case (: (List Int) (list +1 +2 +3))" ..new-line
+ " " "(#Cons x (#Cons y (#Cons z #Nil)))" ..new-line
+ " " "(#Some ($_ i/* x y z))" __paragraph
+ " " "_" ..new-line
+ " " "#None)"))])
({(#Cons value branches)
(do Monad<Meta>
[expansion (expander branches)]
@@ -3132,14 +3142,15 @@
(macro:' #export (^ tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "## Macro-expanding patterns.
- ## It's a special macro meant to be used with 'case'.
- (case (: (List Int) (list +1 +2 +3))
- (^ (list x y z))
- (#Some ($_ i/* x y z))
-
- _
- #None)")])
+ (text$ ($_ "lux text concat"
+ "## Macro-expanding patterns." ..new-line
+ "## It's a special macro meant to be used with 'case'." ..new-line
+ "(case (: (List Int) (list +1 +2 +3))" ..new-line
+ " (^ (list x y z))" ..new-line
+ " (#Some ($_ i/* x y z))"
+ __paragraph
+ " _" ..new-line
+ " #None)"))])
(case tokens
(#Cons [_ (#Form (#Cons pattern #Nil))] (#Cons body branches))
(do Monad<Meta>
@@ -3156,25 +3167,19 @@
(macro:' #export (^or tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "## Or-patterns.
- ## It's a special macro meant to be used with 'case'.
- (type: Weekday
- #Monday
- #Tuesday
- #Wednesday
- #Thursday
- #Friday
- #Saturday
- #Sunday)
-
- (def: (weekend? day)
- (-> Weekday Bit)
- (case day
- (^or #Saturday #Sunday)
- #1
-
- _
- #0))")])
+ (text$ ($_ "lux text concat"
+ "## Or-patterns." ..new-line
+ "## It's a special macro meant to be used with 'case'." ..new-line
+ "(type: Weekday #Monday #Tuesday #Wednesday #Thursday #Friday #Saturday #Sunday)"
+ __paragraph
+ "(def: (weekend? day)" ..new-line
+ " (-> Weekday Bit)" ..new-line
+ " (case day" ..new-line
+ " (^or #Saturday #Sunday)" ..new-line
+ " #1"
+ __paragraph
+ " _" ..new-line
+ " #0))"))])
(case tokens
(^ (list& [_ (#Form patterns)] body branches))
(case patterns
@@ -3200,11 +3205,12 @@
(macro:' #export (let tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "## Creates local bindings.
- ## Can (optionally) use pattern-matching macros when binding.
- (let [x (foo bar)
- y (baz quux)]
- (op x y))")])
+ (text$ ($_ "lux text concat"
+ "## Creates local bindings." ..new-line
+ "## Can (optionally) use pattern-matching macros when binding." ..new-line
+ "(let [x (foo bar)" ..new-line
+ " y (baz quux)]" ..new-line
+ " (op x y))"))])
(case tokens
(^ (list [_ (#Tuple bindings)] body))
(if (multiple? 2 (list/size bindings))
@@ -3225,13 +3231,14 @@
(macro:' #export (function tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "## Syntax for creating functions.
- ## Allows for giving the function itself a name, for the sake of recursion.
- (: (All [a b] (-> a b a))
- (function (_ x y) x))
-
- (: (All [a b] (-> a b a))
- (function (const x y) x))")])
+ (text$ ($_ "lux text concat"
+ "## Syntax for creating functions." ..new-line
+ "## Allows for giving the function itself a name, for the sake of recursion." ..new-line
+ "(: (All [a b] (-> a b a))" ..new-line
+ " (function (_ x y) x))"
+ __paragraph
+ "(: (All [a b] (-> a b a))" ..new-line
+ " (function (const x y) x))"))])
(case (: (Maybe [Text Code (List Code) Code])
(case tokens
(^ (list [_ (#Form (list& [_ (#Identifier ["" name])] head tail))] body))
@@ -3343,15 +3350,16 @@
(macro:' #export (def: tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "## Defines global constants/functions.
- (def: (rejoin-pair pair)
- (-> [Code Code] (List Code))
- (let [[left right] pair]
- (list left right)))
-
- (def: branching-exponent
- Int
- +5)")])
+ (text$ ($_ "lux text concat"
+ "## Defines global constants/functions." ..new-line
+ "(def: (rejoin-pair pair)" ..new-line
+ " (-> [Code Code] (List Code))" ..new-line
+ " (let [[left right] pair]" ..new-line
+ " (list left right)))"
+ __paragraph
+ "(def: branching-exponent" ..new-line
+ " Int" ..new-line
+ " +5)"))])
(let [[export? tokens'] (export^ tokens)
parts (: (Maybe [Code (List Code) (Maybe Code) Code (List [Code Code])])
(case tokens'
@@ -3427,17 +3435,17 @@
(macro:' #export (macro: tokens)
(list [(tag$ ["lux" "doc"])
- (text$ "Macro-definition macro.
-
- (macro: #export (name-of tokens)
- (case tokens
- (^template [<tag>]
- (^ (list [_ (<tag> [prefix name])]))
- (return (list (` [(~ (text$ prefix)) (~ (text$ name))]))))
- ([#Identifier] [#Tag])
-
- _
- (fail \"Wrong syntax for name-of\")))")])
+ (text$ ($_ "lux text concat"
+ "## Macro-definition macro." ..new-line
+ "(macro: #export (name-of tokens)" ..new-line
+ " (case tokens" ..new-line
+ " (^template [<tag>]" ..new-line
+ " (^ (list [_ (<tag> [prefix name])]))" ..new-line
+ " (return (list (` [(~ (text$ prefix)) (~ (text$ name))]))))" ..new-line
+ " ([#Identifier] [#Tag])"
+ __paragraph
+ " _" ..new-line
+ " (fail ''Wrong syntax for name-of'')))"))])
(let [[exported? tokens] (export^ tokens)
name+args+meta+body?? (: (Maybe [Name (List Code) Code Code])
(case tokens
@@ -3474,18 +3482,19 @@
(fail "Wrong syntax for macro:"))))
(macro: #export (signature: tokens)
- {#.doc "## Definition of signatures ala ML.
- (signature: #export (Ord a)
- (: (Equivalence a)
- eq)
- (: (-> a a Bit)
- <)
- (: (-> a a Bit)
- <=)
- (: (-> a a Bit)
- >)
- (: (-> a a Bit)
- >=))"}
+ {#.doc (text$ ($_ "lux text concat"
+ "## Definition of signatures ala ML." ..new-line
+ "(signature: #export (Ord a)" ..new-line
+ " (: (Equivalence a)" ..new-line
+ " eq)" ..new-line
+ " (: (-> a a Bit)" ..new-line
+ " <)" ..new-line
+ " (: (-> a a Bit)" ..new-line
+ " <=)" ..new-line
+ " (: (-> a a Bit)" ..new-line
+ " >)" ..new-line
+ " (: (-> a a Bit)" ..new-line
+ " >=))"))}
(let [[exported? tokens'] (export^ tokens)
?parts (: (Maybe [Name (List Code) Code (List Code)])
(case tokens'
@@ -3566,8 +3575,8 @@
_
(fail <message>)))]
- [and (if (~ pre) (~ post) #0) "'and' requires >=1 clauses." "Short-circuiting \"and\".\n(and #1 #0 #1) ## => #0"]
- [or (if (~ pre) #1 (~ post)) "'or' requires >=1 clauses." "Short-circuiting \"or\".\n(or #1 #0 #1) ## => #1"])
+ [and (if (~ pre) (~ post) #0) "'and' requires >=1 clauses." "Short-circuiting 'and': (and #1 #0 #1) ## => #0"]
+ [or (if (~ pre) #1 (~ post)) "'or' requires >=1 clauses." "Short-circuiting 'or': (or #1 #0 #1) ## => #1"])
(def: (index-of part text)
(-> Text Text (Maybe Nat))
@@ -3591,26 +3600,35 @@
#None
#None))
-(def: (clip1 from text)
+(def: (clip/1 from text)
(-> Nat Text (Maybe Text))
- ("lux text clip" text from ("lux text size" text)))
+ (let [size ("lux text size" text)]
+ (if (n/<= size from)
+ (#.Some ("lux text clip" text from size))
+ #.None)))
-(def: (clip2 from to text)
+(def: (clip/2 from to text)
(-> Nat Nat Text (Maybe Text))
- ("lux text clip" text from to))
+ (if (and (n/<= to from)
+ (n/<= ("lux text size" text) to))
+ (#.Some ("lux text clip" text from to))
+ #.None))
(def: #export (error! message)
- {#.doc "## Causes an error, with the given error message.
- (error! \"OH NO!\")"}
+ {#.doc (text$ ($_ "lux text concat"
+ "## Causes an error, with the given error message." ..new-line
+ "(error! ''OH NO!'')"))}
(-> Text Nothing)
("lux io error" message))
(macro: (default tokens state)
- {#.doc "## Allows you to provide a default value that will be used
- ## if a (Maybe x) value turns out to be #.None.
- (default +20 (#.Some +10)) => +10
-
- (default +20 #.None) => +20"}
+ {#.doc (text$ ($_ "lux text concat"
+ "## Allows you to provide a default value that will be used" ..new-line
+ "## if a (Maybe x) value turns out to be #.None."
+ __paragraph
+ "(default +20 (#.Some +10)) ## => +10"
+ __paragraph
+ "(default +20 #.None) ## => +20"))}
(case tokens
(^ (list else maybe))
(let [g!temp (: Code [dummy-cursor (#Identifier ["" ""])])
@@ -3632,11 +3650,9 @@
(list input)
(#Some idx)
- (list& (default (error! "UNDEFINED")
- (clip2 0 idx input))
+ (list& ("lux text clip" input 0 idx)
(text/split splitter
- (default (error! "UNDEFINED")
- (clip1 (n/+ 1 idx) input))))))
+ ("lux text clip" input (n/+ 1 idx) ("lux text size" input))))))
(def: (nth idx xs)
(All [a]
@@ -3846,7 +3862,7 @@
(#Left "Not expecting any type.")))))
(macro: #export (structure tokens)
- {#.doc "Not meant to be used directly. Prefer \"structure:\"."}
+ {#.doc "Not meant to be used directly. Prefer 'structure:'."}
(do Monad<Meta>
[tokens' (monad/map Monad<Meta> macro-expand tokens)
struct-type get-expected-type
@@ -3883,19 +3899,20 @@
(|> parts list/reverse (list/fold text/compose "")))
(macro: #export (structure: tokens)
- {#.doc "## Definition of structures ala ML.
- (structure: #export Ord<Int> (Ord Int)
- (def: eq Equivalence<Int>)
- (def: (< test subject)
- (lux.< test subject))
- (def: (<= test subject)
- (or (lux.< test subject)
- (lux.= test subject)))
- (def: (lux.> test subject)
- (lux.> test subject))
- (def: (lux.>= test subject)
- (or (lux.> test subject)
- (lux.= test subject))))"}
+ {#.doc (text$ ($_ "lux text concat"
+ "## Definition of structures ala ML." ..new-line
+ "(structure: #export Ord<Int> (Ord Int)" ..new-line
+ " (def: eq Equivalence<Int>)" ..new-line
+ " (def: (< test subject)" ..new-line
+ " (lux.i/< test subject))" ..new-line
+ " (def: (<= test subject)" ..new-line
+ " (or (lux.i/< test subject)" ..new-line
+ " (lux.i/= test subject)))" ..new-line
+ " (def: (> test subject)" ..new-line
+ " (lux.i/> test subject))" ..new-line
+ " (def: (>= test subject)" ..new-line
+ " (or (lux.i/> test subject)" ..new-line
+ " (lux.i/= test subject))))"))}
(let [[exported? tokens'] (export^ tokens)
?parts (: (Maybe [Code (List Code) Code Code (List Code)])
(case tokens'
@@ -3955,23 +3972,20 @@
(structure (~+ definitions)))))))
#None
- (fail "Cannot infer name, so struct must have a name other than \"_\"!"))
+ (fail "Cannot infer name, so struct must have a name other than '_'!"))
#None
(fail "Wrong syntax for structure:"))))
(def: #export (id x)
- {#.doc "Identity function.
-
- Does nothing to it's argument and just returns it."}
+ {#.doc "Identity function. Does nothing to it's argument and just returns it."}
(All [a] (-> a a))
x)
(macro: #export (type: tokens)
- {#.doc "## The type-definition macro.
- (type: (List a)
- #Nil
- (#Cons a (List a)))"}
+ {#.doc (text$ ($_ "lux text concat"
+ "## The type-definition macro." ..new-line
+ "(type: (List a) #Nil (#Cons a (List a)))"))}
(let [[exported? tokens'] (export^ tokens)
[rec? tokens'] (case tokens'
(#Cons [_ (#Tag [_ "rec"])] tokens')
@@ -4128,23 +4142,17 @@
_
(return [#.Nil parts])))
-(def: (split at x)
- (-> Nat Text (Maybe [Text Text]))
- (case [(..clip2 0 at x) (..clip1 at x)]
- [(#.Some pre) (#.Some post)]
- (#.Some [pre post])
-
- _
- #.None))
+(def: (split! at x)
+ (-> Nat Text [Text Text])
+ [("lux text clip" x 0 at)
+ ("lux text clip" x at ("lux text size" x))])
(def: (split-with token sample)
(-> Text Text (Maybe [Text Text]))
(do ..Monad<Maybe>
[index (..index-of token sample)
- pre+post' (split index sample)
- #let [[pre post'] pre+post']
- _+post (split ("lux text size" token) post')
- #let [[_ post] _+post]]
+ #let [[pre post'] (split! index sample)
+ [_ post] (split! ("lux text size" token) post')]]
(wrap [pre post])))
(def: (replace-all pattern value template)
@@ -4197,15 +4205,15 @@
list/reverse
(interpose "/")
text/join)
- clean (|> module (clip1 ups) (default (error! "UNDEFINED")))
+ clean ("lux text clip" module ups ("lux text size" module))
output (case ("lux text size" clean)
0 prefix
_ ($_ text/compose prefix "/" clean))]
(return output))
- (fail ($_ text/compose
- "Cannot climb the module hierarchy...\n"
- "Importing module: " module "\n"
- " Relative Root: " relative-root "\n"))))))
+ (fail ($_ "lux text concat"
+ "Cannot climb the module hierarchy..." ..new-line
+ "Importing module: " module ..new-line
+ " Relative Root: " relative-root ..new-line))))))
(def: (parse-imports nested? relative-root imports)
(-> Bit Text (List Code) (Meta (List Importation)))
@@ -4488,11 +4496,12 @@
))
(macro: #export (^open tokens)
- {#.doc "## Same as the \"open\" macro, but meant to be used as a pattern-matching macro for generating local bindings.
- ## Takes an \"alias\" text for the generated local bindings.
- (def: #export (range (^open \".\") from to)
- (All [a] (-> (Enum a) a a (List a)))
- (range' <= succ from to))"}
+ {#.doc (text$ ($_ "lux text concat"
+ "## Same as the 'open' macro, but meant to be used as a pattern-matching macro for generating local bindings." ..new-line
+ "## Takes an 'alias' text for the generated local bindings." ..new-line
+ "(def: #export (range (^open ''.'') from to)" ..new-line
+ " (All [a] (-> (Enum a) a a (List a)))" ..new-line
+ " (range' <= succ from to))"))}
(case tokens
(^ (list& [_ (#Form (list [_ (#Text alias)]))] body branches))
(do Monad<Meta>
@@ -4505,7 +4514,7 @@
struct-evidence (resolve-type-tags init-type)]
(case struct-evidence
#None
- (fail (text/compose "Can only \"open\" structs: " (type/encode init-type)))
+ (fail (text/compose "Can only 'open' structs: " (type/encode init-type)))
(#Some tags&members)
(do Monad<Meta>
@@ -4538,11 +4547,13 @@
(fail "Wrong syntax for ^open")))
(macro: #export (cond tokens)
- {#.doc "## Branching structures with multiple test conditions.
- (cond (n/even? num) \"even\"
- (n/odd? num) \"odd\"
- ## else-branch
- \"???\")"}
+ {#.doc (text$ ($_ "lux text concat"
+ "## Branching structures with multiple test conditions." ..new-line
+ "(cond (n/even? num) ''even''" ..new-line
+ " (n/odd? num) ''odd''"
+ __paragraph
+ " ## else-branch" ..new-line
+ " ''???'')"))}
(if (n/= 0 (n/% 2 (list/size tokens)))
(fail "cond requires an uneven number of arguments.")
(case (list/reverse tokens)
@@ -4571,16 +4582,16 @@
(enumerate' 0 xs))
(macro: #export (get@ tokens)
- {#.doc "## Accesses the value of a record at a given tag.
- (get@ #field my-record)
-
- ## Can also work with multiple levels of nesting:
- (get@ [#foo #bar #baz] my-record)
-
- ## And, if only the slot/path is given, generates an
- ## accessor function:
- (let [getter (get@ [#foo #bar #baz])]
- (getter my-record))"}
+ {#.doc (text$ ($_ "lux text concat"
+ "## Accesses the value of a record at a given tag." ..new-line
+ "(get@ #field my-record)"
+ __paragraph
+ "## Can also work with multiple levels of nesting:" ..new-line
+ "(get@ [#foo #bar #baz] my-record)"
+ __paragraph
+ "## And, if only the slot/path is given, generates an accessor function:" ..new-line
+ "(let [getter (get@ [#foo #bar #baz])]" ..new-line
+ " (getter my-record))"))}
(case tokens
(^ (list [_ (#Tag slot')] record))
(do Monad<Meta>
@@ -4639,14 +4650,17 @@
[(~ cursor-code) (#.Record #Nil)])))))))
(macro: #export (open: tokens)
- {#.doc "## Opens a structure and generates a definition for each of its members (including nested members).
- ## For example:
- (open: \"i:.\" Number<Int>)
- ## Will generate:
- (def: i:+ (:: Number<Int> +))
- (def: i:- (:: Number<Int> -))
- (def: i:* (:: Number<Int> *))
- ..."}
+ {#.doc (text$ ($_ "lux text concat"
+ "## Opens a structure and generates a definition for each of its members (including nested members)."
+ __paragraph
+ "## For example:" ..new-line
+ "(open: ''i:.'' Number<Int>)"
+ __paragraph
+ "## Will generate:" ..new-line
+ "(def: i:+ (:: Number<Int> +))" ..new-line
+ "(def: i:- (:: Number<Int> -))" ..new-line
+ "(def: i:* (:: Number<Int> *))" ..new-line
+ "..."))}
(case tokens
(^ (list [_ (#Text alias)] struct))
(case struct
@@ -4665,7 +4679,7 @@
(return (list/join decls')))
_
- (fail (text/compose "Can only \"open:\" structs: " (type/encode struct-type)))))
+ (fail (text/compose "Can only 'open:' structs: " (type/encode struct-type)))))
_
(do Monad<Meta>
@@ -4678,26 +4692,22 @@
(fail "Wrong syntax for open:")))
(macro: #export (|>> tokens)
- {#.doc "## Similar to the piping macro, but rather than taking an initial object to work on, creates a function for taking it.
- (|>> (list/map int/encode) (interpose \" \") (fold text/compose \"\"))
- ## =>
- (function (_ <arg>)
- (fold text/compose \"\"
- (interpose \" \"
- (list/map int/encode <arg>))))"}
+ {#.doc (text$ ($_ "lux text concat"
+ "## Similar to the piping macro, but rather than taking an initial object to work on, creates a function for taking it." ..new-line
+ "(|>> (list/map int/encode) (interpose '' '') (fold text/compose ''''))" ..new-line
+ "## =>" ..new-line
+ "(function (_ <arg>) (fold text/compose '''' (interpose '' '' (list/map int/encode <arg>))))"))}
(do Monad<Meta>
[g!_ (gensym "_")
g!arg (gensym "arg")]
(return (list (` (function ((~ g!_) (~ g!arg)) (|> (~ g!arg) (~+ tokens))))))))
(macro: #export (<<| tokens)
- {#.doc "## Similar to the piping macro, but rather than taking an initial object to work on, creates a function for taking it.
- (<<| (fold text/compose \"\") (interpose \" \") (list/map int/encode))
- ## =>
- (function (_ <arg>)
- (fold text/compose \"\"
- (interpose \" \"
- (list/map int/encode <arg>))))"}
+ {#.doc (text$ ($_ "lux text concat"
+ "## Similar to the piping macro, but rather than taking an initial object to work on, creates a function for taking it." ..new-line
+ "(<<| (fold text/compose '''') (interpose '' '') (list/map int/encode))" ..new-line
+ "## =>" ..new-line
+ "(function (_ <arg>) (fold text/compose '''' (interpose '' '' (list/map int/encode <arg>))))"))}
(do Monad<Meta>
[g!_ (gensym "_")
g!arg (gensym "arg")]
@@ -4734,10 +4744,10 @@
_
(fail ($_ text/compose "Wrong syntax for refer @ " current-module
- "\n" (|> options
- (list/map code-to-text)
- (interpose " ")
- (list/fold text/compose "")))))))
+ ..new-line (|> options
+ (list/map code-to-text)
+ (interpose " ")
+ (list/fold text/compose "")))))))
(def: (write-refer module-name [r-defs r-opens])
(-> Text Refer (Meta (List Code)))
@@ -4821,26 +4831,23 @@
(~+ openings)))))
(macro: #export (module: tokens)
- {#.doc "Module-definition macro.
-
- Can take optional annotations and allows the specification of modules to import.
-
- ## Examples
- (.module: {#.doc \"Some documentation...\"}
- [lux #*
- [control
- [\"M\" monad #*]]
- [data
- maybe
- [\".\" name (\"name/.\" Codec<Text,Name>)]
- [\".\" text (\"text/.\" Monoid<Text>)]
- [collection
- [list (\"list/.\" Monad<List>)]]]
- meta
- [macro
- code]]
- [//
- [type (\".\" Equivalence<Type>)]])"}
+ {#.doc (text$ ($_ "lux text concat"
+ "## Module-definition macro."
+ __paragraph
+ "## Can take optional annotations and allows the specification of modules to import."
+ __paragraph
+ "## Example" ..new-line
+ "(.module: {#.doc ''Some documentation...''}" ..new-line
+ " [lux #*" ..new-line
+ " [control" ..new-line
+ " [''M'' monad #*]]" ..new-line
+ " [data" ..new-line
+ " maybe" ..new-line
+ " [''.'' name (''name/.'' Codec<Text,Name>)]]" ..new-line
+ " [macro" ..new-line
+ " code]]" ..new-line
+ " [//" ..new-line
+ " [type (''.'' Equivalence<Type>)]])"))}
(do Monad<Meta>
[#let [[_meta _imports] (: [(List [Code Code]) (List Code)]
(case tokens
@@ -4866,11 +4873,12 @@
(wrap (#Cons =module =refers))))
(macro: #export (:: tokens)
- {#.doc "## Allows accessing the value of a structure's member.
- (:: Codec<Text,Int> encode)
-
- ## Also allows using that value as a function.
- (:: Codec<Text,Int> encode +123)"}
+ {#.doc (text$ ($_ "lux text concat"
+ "## Allows accessing the value of a structure's member." ..new-line
+ "(:: Codec<Text,Int> encode)"
+ __paragraph
+ "## Also allows using that value as a function." ..new-line
+ "(:: Codec<Text,Int> encode +123)"))}
(case tokens
(^ (list struct [_ (#Identifier member)]))
(return (list (` (let [(^open ".") (~ struct)] (~ (identifier$ member))))))
@@ -4882,19 +4890,16 @@
(fail "Wrong syntax for ::")))
(macro: #export (set@ tokens)
- {#.doc "## Sets the value of a record at a given tag.
- (set@ #name \"Lux\" lang)
-
- ## Can also work with multiple levels of nesting:
- (set@ [#foo #bar #baz] value my-record)
-
- ## And, if only the slot/path and (optionally) the value are given, generates a
- ## mutator function:
- (let [setter (set@ [#foo #bar #baz] value)]
- (setter my-record))
-
- (let [setter (set@ [#foo #bar #baz])]
- (setter value my-record))"}
+ {#.doc (text$ ($_ "lux text concat"
+ "## Sets the value of a record at a given tag." ..new-line
+ "(set@ #name ''Lux'' lang)"
+ __paragraph
+ "## Can also work with multiple levels of nesting:" ..new-line
+ "(set@ [#foo #bar #baz] value my-record)"
+ __paragraph
+ "## And, if only the slot/path and (optionally) the value are given, generates a mutator function:" ..new-line
+ "(let [setter (set@ [#foo #bar #baz] value)] (setter my-record))" ..new-line
+ "(let [setter (set@ [#foo #bar #baz])] (setter value my-record))"))}
(case tokens
(^ (list [_ (#Tag slot')] value record))
(do Monad<Meta>
@@ -4972,19 +4977,16 @@
(fail "Wrong syntax for set@")))
(macro: #export (update@ tokens)
- {#.doc "## Modifies the value of a record at a given tag, based on some function.
- (update@ #age inc person)
-
- ## Can also work with multiple levels of nesting:
- (update@ [#foo #bar #baz] func my-record)
-
- ## And, if only the slot/path and (optionally) the value are given, generates a
- ## mutator function:
- (let [updater (update@ [#foo #bar #baz] func)]
- (updater my-record))
-
- (let [updater (update@ [#foo #bar #baz])]
- (updater func my-record))"}
+ {#.doc (text$ ($_ "lux text concat"
+ "## Modifies the value of a record at a given tag, based on some function." ..new-line
+ "(update@ #age inc person)"
+ __paragraph
+ "## Can also work with multiple levels of nesting:" ..new-line
+ "(update@ [#foo #bar #baz] func my-record)"
+ __paragraph
+ "## And, if only the slot/path and (optionally) the value are given, generates a mutator function:" ..new-line
+ "(let [updater (update@ [#foo #bar #baz] func)] (updater my-record))" ..new-line
+ "(let [updater (update@ [#foo #bar #baz])] (updater func my-record))"))}
(case tokens
(^ (list [_ (#Tag slot')] fun record))
(do Monad<Meta>
@@ -5048,41 +5050,40 @@
(fail "Wrong syntax for update@")))
(macro: #export (^template tokens)
- {#.doc "## It's similar to do-template, but meant to be used during pattern-matching.
- (def: (beta-reduce env type)
- (-> (List Type) Type Type)
- (case type
- (#.Primitive name params)
- (#.Primitive name (list/map (beta-reduce env) params))
-
- (^template [<tag>]
- (<tag> left right)
- (<tag> (beta-reduce env left) (beta-reduce env right)))
- ([#.Sum] [#.Product])
-
- (^template [<tag>]
- (<tag> left right)
- (<tag> (beta-reduce env left) (beta-reduce env right)))
- ([#.Function]
- [#.Apply])
-
- (^template [<tag>]
- (<tag> old-env def)
- (case old-env
- #.Nil
- (<tag> env def)
-
- _
- type))
- ([#.UnivQ]
- [#.ExQ])
-
- (#.Parameter idx)
- (default type (list.nth idx env))
-
- _
- type
- ))"}
+ {#.doc (text$ ($_ "lux text concat"
+ "## It's similar to do-template, but meant to be used during pattern-matching." ..new-line
+ "(def: (beta-reduce env type)" ..new-line
+ " (-> (List Type) Type Type)" ..new-line
+ " (case type" ..new-line
+ " (#.Primitive name params)" ..new-line
+ " (#.Primitive name (list/map (beta-reduce env) params))"
+ __paragraph
+ " (^template [<tag>]" ..new-line
+ " (<tag> left right)" ..new-line
+ " (<tag> (beta-reduce env left) (beta-reduce env right)))" ..new-line
+ " ([#.Sum] [#.Product])"
+ __paragraph
+ " (^template [<tag>]" ..new-line
+ " (<tag> left right)" ..new-line
+ " (<tag> (beta-reduce env left) (beta-reduce env right)))" ..new-line
+ " ([#.Function] [#.Apply])"
+ __paragraph
+ " (^template [<tag>]" ..new-line
+ " (<tag> old-env def)" ..new-line
+ " (case old-env" ..new-line
+ " #.Nil" ..new-line
+ " (<tag> env def)"
+ __paragraph
+ " _" ..new-line
+ " type))" ..new-line
+ " ([#.UnivQ] [#.ExQ])"
+ __paragraph
+ " (#.Parameter idx)" ..new-line
+ " (default type (list.nth idx env))"
+ __paragraph
+ " _" ..new-line
+ " type" ..new-line
+ " ))"))}
(case tokens
(^ (list& [_ (#Form (list& [_ (#Tuple bindings)] templates))]
[_ (#Form data)]
@@ -5158,17 +5159,7 @@
(def: (text/encode original)
(-> Text Text)
- (let [escaped (|> original
- (replace-all "\t" "\\t")
- (replace-all "\v" "\\v")
- (replace-all "\b" "\\b")
- (replace-all "\n" "\\n")
- (replace-all "\r" "\\r")
- (replace-all "\f" "\\f")
- (replace-all "\"" "\\\"")
- (replace-all "\\" "\\\\")
- )]
- ($_ text/compose "\"" escaped "\"")))
+ ($_ text/compose ..double-quote original ..double-quote))
(do-template [<name> <extension> <doc>]
[(def: #export (<name> value)
@@ -5205,7 +5196,7 @@
(-> Nat Cursor Cursor Text)
(if (n/= old-line new-line)
(text/join (repeat (.int (n/- old-column new-column)) " "))
- (let [extra-lines (text/join (repeat (.int (n/- old-line new-line)) "\n"))
+ (let [extra-lines (text/join (repeat (.int (n/- old-line new-line)) ..new-line))
space-padding (text/join (repeat (.int (n/- baseline new-column)) " "))]
(text/compose extra-lines space-padding))))
@@ -5271,27 +5262,28 @@
(case fragment
(#Doc-Comment comment)
(|> comment
- (text/split "\n")
- (list/map (function (_ line) ($_ text/compose "## " line "\n")))
+ (text/split ..new-line)
+ (list/map (function (_ line) ($_ text/compose "## " line ..new-line)))
text/join)
(#Doc-Example example)
(let [baseline (find-baseline-column example)
[cursor _] example
[_ text] (doc-example->Text (with-baseline baseline cursor) baseline example)]
- (text/compose text "\n\n"))))
+ (text/compose text __paragraph))))
(macro: #export (doc tokens)
- {#.doc "## Creates code documentation, embedding text as comments and properly formatting the forms it's being given.
-
- ## For Example:
- (doc \"Allows arbitrary looping, using the \\\"recur\\\" form to re-start the loop.
- Can be used in monadic code to create monadic loops.\"
- (loop [count +0
- x init]
- (if (< +10 count)
- (recur (inc count) (f x))
- x)))"}
+ {#.doc (text$ ($_ "lux text concat"
+ "## Creates code documentation, embedding text as comments and properly formatting the forms it's being given."
+ __paragraph
+ "## For Example:" ..new-line
+ "(doc ''Allows arbitrary looping, using the 'recur' form to re-start the loop.''" ..new-line
+ " ''Can be used in monadic code to create monadic loops.''" ..new-line
+ " (loop [count +0" ..new-line
+ " x init]" ..new-line
+ " (if (< +10 count)" ..new-line
+ " (recur (inc count) (f x))" ..new-line
+ " x)))"))}
(return (list (` [(~ cursor-code)
(#.Text (~ (|> tokens
(list/map (|>> identify-doc-fragment doc-fragment->Text))
@@ -5350,7 +5342,7 @@
(identifier$ [module name])))
(macro: #export (loop tokens)
- {#.doc (doc "Allows arbitrary looping, using the \"recur\" form to re-start the loop."
+ {#.doc (doc "Allows arbitrary looping, using the 'recur' form to re-start the loop."
"Can be used in monadic code to create monadic loops."
(loop [count +0
x init]
@@ -5493,18 +5485,18 @@
(compare <text> (:: Code/encode encode <expr>))
(compare #1 (:: Equivalence<Code> = <expr> <expr>))]
- [(bit #1) "#1" [_ (#.Bit #1)]]
- [(bit #0) "#0" [_ (#.Bit #0)]]
+ [(bit #1) "#1" [_ (#.Bit #1)]]
+ [(bit #0) "#0" [_ (#.Bit #0)]]
[(int +123) "+123" [_ (#.Int +123)]]
[(frac +123.0) "+123.0" [_ (#.Frac +123.0)]]
- [(text "\n") "\"\\n\"" [_ (#.Text "\n")]]
- [(tag ["yolo" "lol"]) "#yolo.lol" [_ (#.Tag ["yolo" "lol"])]]
- [(identifier ["yolo" "lol"]) "yolo.lol" [_ (#.Identifier ["yolo" "lol"])]]
+ [(text "123") "'123'" [_ (#.Text "123")]]
+ [(tag ["yolo" "lol"]) "#yolo.lol" [_ (#.Tag ["yolo" "lol"])]]
+ [(identifier ["yolo" "lol"]) "yolo.lol" [_ (#.Identifier ["yolo" "lol"])]]
[(form (list (bit #1) (int +123))) "(#1 +123)" (^ [_ (#.Form (list [_ (#.Bit #1)] [_ (#.Int +123)]))])]
[(tuple (list (bit #1) (int +123))) "[#1 +123]" (^ [_ (#.Tuple (list [_ (#.Bit #1)] [_ (#.Int +123)]))])]
[(record (list [(bit #1) (int +123)])) "{#1 +123}" (^ [_ (#.Record (list [[_ (#.Bit #1)] [_ (#.Int +123)]]))])]
- [(local-tag "lol") "#lol" [_ (#.Tag ["" "lol"])]]
- [(local-identifier "lol") "lol" [_ (#.Identifier ["" "lol"])]]
+ [(local-tag "lol") "#lol" [_ (#.Tag ["" "lol"])]]
+ [(local-identifier "lol") "lol" [_ (#.Identifier ["" "lol"])]]
)]
(test-all <tests>))))}
(case tokens
@@ -5610,7 +5602,7 @@
(wrap (list pattern')))
_
- (fail "Wrong syntax for \"static\".")))
+ (fail "Wrong syntax for 'static'.")))
(type: Multi-Level-Case
[Code (List [Code Code])])
@@ -5763,7 +5755,7 @@
(fail "Wrong syntax for $")))
(def: #export (is? reference sample)
- {#.doc (doc "Tests whether the 2 values are identical (not just \"equal\")."
+ {#.doc (doc "Tests whether the 2 values are identical (not just 'equal')."
"This one should succeed:"
(let [value +5]
(is? value value))
@@ -5945,7 +5937,7 @@
(^ (list (~+ (list/map (|>> [""] identifier$) args))))
(#.Right [(~ g!compiler)
(list (~+ (list/map (function (_ template)
- (` (` (~ (replace-syntax rep-env template)))))
+ (` (`' (~ (replace-syntax rep-env template)))))
input-templates)))])
(~ g!_)
@@ -5961,7 +5953,6 @@
(^multi (^ (list [_ (#Text input)]))
(n/= 1 ("lux text size" input)))
(|> ("lux text char" input 0)
- (default (undefined))
nat$ list
[compiler] #Right)