aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/lux.lux')
-rw-r--r--stdlib/source/lux.lux172
1 files changed, 86 insertions, 86 deletions
diff --git a/stdlib/source/lux.lux b/stdlib/source/lux.lux
index 51dff8142..c9a800741 100644
--- a/stdlib/source/lux.lux
+++ b/stdlib/source/lux.lux
@@ -1096,7 +1096,7 @@
(def:'' (text/= x y)
#;Nil
(#Function Text (#Function Text Bool))
- (_lux_proc ["text" "="] [x y]))
+ ("lux text =" x y))
(def:'' (get-rep key env)
#;Nil
@@ -1158,7 +1158,7 @@
pairs))
[_ (#Form (#Cons [_ (#Tag "lux" "Bound")] (#Cons [_ (#Nat idx)] #Nil)))]
- (form$ (#Cons (tag$ ["lux" "Bound"]) (#Cons (nat$ (_lux_proc ["nat" "+"] [+2 idx])) #Nil)))
+ (form$ (#Cons (tag$ ["lux" "Bound"]) (#Cons (nat$ ("lux nat +" +2 idx)) #Nil)))
[_ (#Form members)]
(form$ (map update-bounds members))
@@ -1209,7 +1209,7 @@
#;Nil
(#UnivQ #Nil
(#Function ($' List (#Bound +1)) Int))
- (fold (function'' [_ acc] (_lux_proc ["int" "+"] [1 acc])) 0 list))
+ (fold (function'' [_ acc] ("lux int +" 1 acc)) 0 list))
(macro:' #export (All tokens)
(#Cons [(tag$ ["lux" "doc"])
@@ -1248,11 +1248,11 @@
body'
[false _]
- (replace-syntax (#Cons [self-name (make-bound (_lux_proc ["nat" "*"]
- [+2 (_lux_proc ["nat" "-"]
- [(_lux_proc ["int" "to-nat"]
- [(length names)])
- +1])]))]
+ (replace-syntax (#Cons [self-name (make-bound ("lux nat *"
+ +2 ("lux nat -"
+ ("lux int to-nat"
+ (length names))
+ +1)))]
#Nil)
body')})
#Nil)))))
@@ -1300,11 +1300,10 @@
body'
[false _]
- (replace-syntax (#Cons [self-name (make-bound (_lux_proc ["nat" "*"]
- [+2 (_lux_proc ["nat" "-"]
- [(_lux_proc ["int" "to-nat"]
- [(length names)])
- +1])]))]
+ (replace-syntax (#Cons [self-name (make-bound ("lux nat *"
+ +2 ("lux nat -"
+ ("lux int to-nat" (length names))
+ +1)))]
#Nil)
body')})
#Nil)))))
@@ -1765,12 +1764,12 @@
Useful for debugging.")])
(-> Text Unit)
- (_lux_proc ["io" "log"] [message]))
+ ("lux io log" message))
(def:''' (text/compose x y)
#Nil
(-> Text Text Text)
- (_lux_proc ["text" "append"] [x y]))
+ ("lux text append" x y))
(def:''' (ident/encode ident)
#Nil
@@ -2197,7 +2196,7 @@
(let' [apply ("lux check" (-> RepEnv ($' List Code))
(function' [env] (map (apply-template env) templates)))
num-bindings (length bindings')]
- (if (every? (function' [sample] (_lux_proc ["int" "="] [num-bindings sample]))
+ (if (every? (function' [sample] ("lux int =" num-bindings sample))
(map length data'))
(|> data'
(join-map (. apply (make-env bindings')))
@@ -2210,47 +2209,48 @@
_
(fail "Wrong syntax for do-template")}))
-(do-template [<type> <category> <=-name> <lt-name> <lte-name> <gt-name> <gte-name>
+(do-template [<type>
+ <=-proc> <lt-proc> <=-name> <lt-name> <lte-name> <gt-name> <gte-name>
<eq-doc> <<-doc> <<=-doc> <>-doc> <>=-doc>]
[(def:''' #export (<=-name> test subject)
(list [(tag$ ["lux" "doc"]) (text$ <eq-doc>)])
(-> <type> <type> Bool)
- (_lux_proc [<category> "="] [subject test]))
+ (<=-proc> subject test))
(def:''' #export (<lt-name> test subject)
(list [(tag$ ["lux" "doc"]) (text$ <<-doc>)])
(-> <type> <type> Bool)
- (_lux_proc [<category> "<"] [subject test]))
+ (<lt-proc> subject test))
(def:''' #export (<lte-name> test subject)
(list [(tag$ ["lux" "doc"]) (text$ <<=-doc>)])
(-> <type> <type> Bool)
- (if (_lux_proc [<category> "<"] [subject test])
+ (if (<lt-proc> subject test)
true
- (_lux_proc [<category> "="] [subject test])))
+ (<=-proc> subject test)))
(def:''' #export (<gt-name> test subject)
(list [(tag$ ["lux" "doc"]) (text$ <>-doc>)])
(-> <type> <type> Bool)
- (_lux_proc [<category> "<"] [test subject]))
+ (<lt-proc> test subject))
(def:''' #export (<gte-name> test subject)
(list [(tag$ ["lux" "doc"]) (text$ <>=-doc>)])
(-> <type> <type> Bool)
- (if (_lux_proc [<category> "<"] [test subject])
+ (if (<lt-proc> test subject)
true
- (_lux_proc [<category> "="] [subject test])))]
+ (<=-proc> subject test)))]
- [ Nat "nat" n.= n.< n.<= n.> n.>=
+ [ Nat "lux nat =" "lux nat <" n.= n.< n.<= n.> n.>=
"Nat(ural) equality." "Nat(ural) less-than." "Nat(ural) less-than-equal." "Nat(ural) greater-than." "Nat(ural) greater-than-equal."]
- [ Int "int" i.= i.< i.<= i.> i.>=
+ [ Int "lux int =" "lux int <" i.= i.< i.<= i.> i.>=
"Int(eger) equality." "Int(eger) less-than." "Int(eger) less-than-equal." "Int(eger) greater-than." "Int(eger) greater-than-equal."]
- [ Deg "deg" d.= d.< d.<= d.> d.>=
+ [ Deg "lux deg =" "lux deg <" d.= d.< d.<= d.> d.>=
"Deg(ree) equality." "Deg(ree) less-than." "Deg(ree) less-than-equal." "Deg(ree) greater-than." "Deg(ree) greater-than-equal."]
- [Frac "frac" f.= f.< f.<= f.> f.>=
+ [Frac "lux frac =" "lux frac <" f.= f.< f.<= f.> f.>=
"Frac(tion) equality." "Frac(tion) less-than." "Frac(tion) less-than-equal." "Frac(tion) greater-than." "Frac(tion) greater-than-equal."]
)
@@ -2258,41 +2258,41 @@
[(def:''' #export (<name> param subject)
(list [(tag$ ["lux" "doc"]) (text$ <doc>)])
(-> <type> <type> <type>)
- (_lux_proc <op> [subject param]))]
+ (<op> subject param))]
- [ Nat n.+ [ "nat" "+"] "Nat(ural) addition."]
- [ Nat n.- [ "nat" "-"] "Nat(ural) substraction."]
- [ Nat n.* [ "nat" "*"] "Nat(ural) multiplication."]
- [ Nat n./ [ "nat" "/"] "Nat(ural) division."]
- [ Nat n.% [ "nat" "%"] "Nat(ural) remainder."]
+ [ Nat n.+ "lux nat +" "Nat(ural) addition."]
+ [ Nat n.- "lux nat -" "Nat(ural) substraction."]
+ [ Nat n.* "lux nat *" "Nat(ural) multiplication."]
+ [ Nat n./ "lux nat /" "Nat(ural) division."]
+ [ Nat n.% "lux nat %" "Nat(ural) remainder."]
- [ Int i.+ [ "int" "+"] "Int(eger) addition."]
- [ Int i.- [ "int" "-"] "Int(eger) substraction."]
- [ Int i.* [ "int" "*"] "Int(eger) multiplication."]
- [ Int i./ [ "int" "/"] "Int(eger) division."]
- [ Int i.% [ "int" "%"] "Int(eger) remainder."]
-
- [ Deg d.+ [ "deg" "+"] "Deg(ree) addition."]
- [ Deg d.- [ "deg" "-"] "Deg(ree) substraction."]
- [ Deg d.* [ "deg" "*"] "Deg(ree) multiplication."]
- [ Deg d./ [ "deg" "/"] "Deg(ree) division."]
- [ Deg d.% [ "deg" "%"] "Deg(ree) remainder."]
+ [ Int i.+ "lux int +" "Int(eger) addition."]
+ [ Int i.- "lux int -" "Int(eger) substraction."]
+ [ Int i.* "lux int *" "Int(eger) multiplication."]
+ [ Int i./ "lux int /" "Int(eger) division."]
+ [ Int i.% "lux int %" "Int(eger) remainder."]
+
+ [ Deg d.+ "lux deg +" "Deg(ree) addition."]
+ [ Deg d.- "lux deg -" "Deg(ree) substraction."]
+ [ Deg d.* "lux deg *" "Deg(ree) multiplication."]
+ [ Deg d./ "lux deg /" "Deg(ree) division."]
+ [ Deg d.% "lux deg %" "Deg(ree) remainder."]
- [Frac f.+ ["frac" "+"] "Frac(tion) addition."]
- [Frac f.- ["frac" "-"] "Frac(tion) substraction."]
- [Frac f.* ["frac" "*"] "Frac(tion) multiplication."]
- [Frac f./ ["frac" "/"] "Frac(tion) division."]
- [Frac f.% ["frac" "%"] "Frac(tion) remainder."]
+ [Frac f.+ "lux frac +" "Frac(tion) addition."]
+ [Frac f.- "lux frac -" "Frac(tion) substraction."]
+ [Frac f.* "lux frac *" "Frac(tion) multiplication."]
+ [Frac f./ "lux frac /" "Frac(tion) division."]
+ [Frac f.% "lux frac %" "Frac(tion) remainder."]
)
(do-template [<type> <name> <op> <doc>]
[(def:''' #export (<name> param subject)
(list [(tag$ ["lux" "doc"]) (text$ <doc>)])
(-> Nat <type> <type>)
- (_lux_proc <op> [subject param]))]
+ (<op> subject param))]
- [ Deg d.scale [ "deg" "scale"] "Deg(ree) scale."]
- [ Deg d.reciprocal [ "deg" "reciprocal"] "Deg(ree) reciprocal."]
+ [ Deg d.scale "lux deg scale" "Deg(ree) scale."]
+ [ Deg d.reciprocal "lux deg reciprocal" "Deg(ree) reciprocal."]
)
(do-template [<name> <type> <test> <doc>]
@@ -2329,7 +2329,7 @@
+1 "1" +2 "2" +3 "3"
+4 "4" +5 "5" +6 "6"
+7 "7" +8 "8" +9 "9"
- _ (_lux_proc ["io" "error"] ["undefined"])}))
+ _ ("lux io error" "undefined")}))
(def:''' (nat/encode value)
#Nil
@@ -2341,11 +2341,11 @@
_
(let' [loop ("lux check" (-> Nat Text Text)
(function' recur [input output]
- (if (_lux_proc ["nat" "="] [input +0])
- (_lux_proc ["text" "append"] ["+" output])
- (recur (_lux_proc ["nat" "/"] [input +10])
- (_lux_proc ["text" "append"] [(digit-to-text (_lux_proc ["nat" "%"] [input +10]))
- output])))))]
+ (if ("lux nat =" input +0)
+ ("lux text append" "+" output)
+ (recur ("lux nat /" input +10)
+ ("lux text append" (digit-to-text ("lux nat %" input +10))
+ output)))))]
(loop value ""))}))
(def:''' (int/abs value)
@@ -2366,17 +2366,17 @@
(("lux check" (-> Int Text Text)
(function' recur [input output]
(if (i.= 0 input)
- (_lux_proc ["text" "append"] [sign output])
+ ("lux text append" sign output)
(recur (i./ 10 input)
- (_lux_proc ["text" "append"] [(|> input (i.% 10) ("lux coerce" Nat) digit-to-text)
- output])))))
+ ("lux text append" (|> input (i.% 10) ("lux coerce" Nat) digit-to-text)
+ output)))))
(|> value (i./ 10) int/abs)
(|> value (i.% 10) int/abs ("lux coerce" Nat) digit-to-text)))))
(def:''' (frac/encode x)
#Nil
(-> Frac Text)
- (_lux_proc ["frac" "encode"] [x]))
+ ("lux frac encode" x))
(def:''' (multiple? div n)
#Nil
@@ -2812,7 +2812,7 @@
(int/encode value)
[_ (#Deg value)]
- (_lux_proc ["io" "error"] ["Undefined behavior."])
+ ("lux io error" "Undefined behavior.")
[_ (#Frac value)]
(frac/encode value)
@@ -3358,25 +3358,25 @@
(do-template [<name> <proc> <start>]
[(def: (<name> part text)
(-> Text Text (Maybe Nat))
- (_lux_proc ["text" <proc>] [text part <start>]))]
+ (<proc> text part <start>))]
- [index-of "index" +0]
- [last-index-of "last-index" (_lux_proc ["text" "size"] [text])]
+ [index-of "lux text index" +0]
+ [last-index-of "lux text last-index" ("lux text size" text)]
)
(def: (clip1 from text)
(-> Nat Text (Maybe Text))
- (_lux_proc ["text" "clip"] [text from (_lux_proc ["text" "size"] [text])]))
+ ("lux text clip" text from ("lux text size" text)))
(def: (clip2 from to text)
(-> Nat Nat Text (Maybe Text))
- (_lux_proc ["text" "clip"] [text from to]))
+ ("lux text clip" text from to))
(def: #export (error! message)
{#;doc "## Causes an error, with the given error message.
(error! \"OH NO!\")"}
(-> Text Bottom)
- (_lux_proc ["io" "error"] [message]))
+ ("lux io error" message))
(macro: (default tokens state)
{#;doc "## Allows you to provide a default value that will be used
@@ -3478,7 +3478,7 @@
(#Function (beta-reduce env ?input) (beta-reduce env ?output))
(#Bound idx)
- (case (nth (_lux_proc ["nat" "to-int"] [idx]) env)
+ (case (nth ("lux nat to-int" idx) env)
(#Some bound)
bound
@@ -4059,7 +4059,7 @@
(def: (replace-all pattern value template)
(-> Text Text Text Text)
- (_lux_proc ["text" "replace-all"] [template pattern value]))
+ ("lux text replace-all" template pattern value))
(def: (clean-module module)
(-> Text (Meta Text))
@@ -4989,10 +4989,10 @@
(do-template [<name> <from> <to> <proc>]
[(def: #export (<name> n)
(-> <from> <to>)
- (_lux_proc <proc> [n]))]
+ (<proc> [n]))]
- [frac-to-int Frac Int ["frac" "to-int"]]
- [int-to-frac Int Frac ["int" "to-frac"]]
+ [frac-to-int Frac Int "lux frac to-int"]
+ [int-to-frac Int Frac "lux int to-frac"]
)
(def: (find-baseline-column code)
@@ -5068,12 +5068,12 @@
(do-template [<name> <op> <from> <to>]
[(def: #export (<name> input)
(-> <from> <to>)
- (_lux_proc <op> [input]))]
+ (<op> input))]
- [int-to-nat ["int" "to-nat"] Int Nat]
- [nat-to-int ["nat" "to-int"] Nat Int]
- [frac-to-deg ["frac" "to-deg"] Frac Deg]
- [deg-to-frac ["deg" "to-frac"] Deg Frac]
+ [int-to-nat "lux int to-nat" Int Nat]
+ [nat-to-int "lux nat to-int" Nat Int]
+ [frac-to-deg "lux frac to-deg" Frac Deg]
+ [deg-to-frac "lux deg to-frac" Deg Frac]
)
(def: (repeat n x)
@@ -5092,11 +5092,11 @@
(def: (text/size x)
(-> Text Nat)
- (_lux_proc ["text" "size"] [x]))
+ ("lux text size" x))
(def: (text/trim x)
(-> Text Text)
- (_lux_proc ["text" "trim"] [x]))
+ ("lux text trim" x))
(def: (update-cursor [file line column] code-text)
(-> Cursor Text Cursor)
@@ -5144,7 +5144,7 @@
[#Record "{" "}" rejoin-all-pairs])
[new-cursor (#Deg value)]
- (_lux_proc ["io" "error"] ["Undefined behavior."])
+ ("lux io error" "Undefined behavior.")
))
(def: (with-baseline baseline [file line column])
@@ -5663,7 +5663,7 @@
"This one should fail:"
(is 5 (i.+ 2 3)))}
(All [a] (-> a a Bool))
- (_lux_proc ["lux" "is"] [reference sample]))
+ ("lux is" reference sample))
(macro: #export (^@ tokens)
{#;doc (doc "Allows you to simultaneously bind and de-structure a value."
@@ -5858,8 +5858,8 @@
(macro: #export (char tokens compiler)
(case tokens
(^multi (^ (list [_ (#Text input)]))
- (n.= +1 (_lux_proc ["text" "size"] [input])))
- (|> (_lux_proc ["text" "char"] [input +0])
+ (n.= +1 ("lux text size" input)))
+ (|> ("lux text char" input +0)
(default (undefined))
nat$ list
[compiler] #;Right)