From 0c0472862f5c1e543e6c5614a4cd112ac7d4cc13 Mon Sep 17 00:00:00 2001 From: Eduardo Julian Date: Sat, 14 Jul 2018 02:59:41 -0400 Subject: - New syntax for bit values: "#0" and "#1", instead of "false" and "true". - Small improvements to lux-mode. --- stdlib/source/lux.lux | 262 ++++++++++++++++++++++++++------------------------ 1 file changed, 135 insertions(+), 127 deletions(-) (limited to 'stdlib/source/lux.lux') diff --git a/stdlib/source/lux.lux b/stdlib/source/lux.lux index 2f2649758..226545576 100644 --- a/stdlib/source/lux.lux +++ b/stdlib/source/lux.lux @@ -1,4 +1,3 @@ -## Basic types ("lux def" dummy-cursor ("lux check" (+2 (+0 "#Text" (+0)) (+2 (+0 "#I64" (+1 (+0 "#Nat" (+0)) (+0))) @@ -6,7 +5,7 @@ ["" +0 +0]) [["" +0 +0] (+10 (+1 [[["" +0 +0] (+7 ["lux" "export?"])] - [["" +0 +0] (+0 true)]] + [["" +0 +0] (+0 #1)]] (+0)))]) ## (type: Any @@ -16,9 +15,9 @@ (+8 (+0) (+4 +1))) [dummy-cursor (+10 (+1 [[dummy-cursor (+7 ["lux" "type?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (+1 [[dummy-cursor (+7 ["lux" "export?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (+1 [[dummy-cursor (+7 ["lux" "doc"])] [dummy-cursor (+5 "The type of things whose type does not matter. @@ -32,9 +31,9 @@ (+7 (+0) (+4 +1))) [dummy-cursor (+10 (+1 [[dummy-cursor (+7 ["lux" "type?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (+1 [[dummy-cursor (+7 ["lux" "export?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (+1 [[dummy-cursor (+7 ["lux" "doc"])] [dummy-cursor (+5 "The type of things whose type is unknown or undefined. @@ -54,9 +53,9 @@ (+9 (+4 +1) (+4 +0)))))) [dummy-cursor (+10 (+1 [[dummy-cursor (+7 ["lux" "type?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (+1 [[dummy-cursor (+7 ["lux" "export?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (+1 [[dummy-cursor (+7 ["lux" "tags"])] [dummy-cursor (+9 (+1 [dummy-cursor (+5 "Nil")] (+1 [dummy-cursor (+5 "Cons")] (+0))))]] (+1 [[dummy-cursor (+7 ["lux" "type-args"])] @@ -70,9 +69,9 @@ (+0 "#Bit" #Nil)) [dummy-cursor (+10 (#Cons [[dummy-cursor (+7 ["lux" "type?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "export?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "doc"])] [dummy-cursor (+5 "Your standard, run-of-the-mill boolean values (as bits).")]] #Nil))))]) @@ -83,9 +82,9 @@ (+0 "#I64" (#Cons (+4 +1) #Nil)))) [dummy-cursor (+10 (#Cons [[dummy-cursor (+7 ["lux" "type?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "export?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "doc"])] [dummy-cursor (+5 "64-bit integers without any semantics.")]] #Nil))))]) @@ -95,9 +94,9 @@ (+0 "#I64" (#Cons (+0 "#Nat" #Nil) #Nil))) [dummy-cursor (+10 (#Cons [[dummy-cursor (+7 ["lux" "type?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "export?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "doc"])] [dummy-cursor (+5 "Natural numbers (unsigned integers). @@ -109,9 +108,9 @@ (+0 "#I64" (#Cons (+0 "#Int" #Nil) #Nil))) [dummy-cursor (+10 (#Cons [[dummy-cursor (+7 ["lux" "type?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "export?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "doc"])] [dummy-cursor (+5 "Your standard, run-of-the-mill integer numbers.")]] #Nil))))]) @@ -121,9 +120,9 @@ (+0 "#I64" (#Cons (+0 "#Rev" #Nil) #Nil))) [dummy-cursor (+10 (#Cons [[dummy-cursor (+7 ["lux" "type?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "export?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "doc"])] [dummy-cursor (+5 "Fractional numbers that live in the interval [0,1). @@ -135,9 +134,9 @@ (+0 "#Frac" #Nil)) [dummy-cursor (+10 (#Cons [[dummy-cursor (+7 ["lux" "type?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "export?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "doc"])] [dummy-cursor (+5 "Your standard, run-of-the-mill floating-point (fractional) numbers.")]] #Nil))))]) @@ -147,9 +146,9 @@ (+0 "#Text" #Nil)) [dummy-cursor (+10 (#Cons [[dummy-cursor (+7 ["lux" "type?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "export?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "doc"])] [dummy-cursor (+5 "Your standard, run-of-the-mill string values.")]] #Nil))))]) @@ -159,9 +158,9 @@ (+2 Text Text)) [dummy-cursor (+10 (#Cons [[dummy-cursor (+7 ["lux" "type?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "export?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "doc"])] [dummy-cursor (+5 "An identifier. @@ -180,9 +179,9 @@ (+4 +1)))) [dummy-cursor (+10 (#Cons [[dummy-cursor (+7 ["lux" "type?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "export?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "tags"])] [dummy-cursor (+9 (#Cons [dummy-cursor (+5 "None")] (#Cons [dummy-cursor (+5 "Some")] #Nil)))]] (#Cons [[dummy-cursor (+7 ["lux" "type-args"])] @@ -238,9 +237,9 @@ ("lux check type" (+9 (+4 +1) (+4 +0))))) [dummy-cursor (+10 (#Cons [[dummy-cursor (+7 ["lux" "type?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "export?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "tags"])] [dummy-cursor (+9 (#Cons [dummy-cursor (+5 "Primitive")] (#Cons [dummy-cursor (+5 "Sum")] @@ -257,7 +256,7 @@ (#Cons [[dummy-cursor (+7 ["lux" "doc"])] [dummy-cursor (+5 "This type represents the data-structures that are used to specify types themselves.")]] (#Cons [[dummy-cursor (+7 ["lux" "type-rec?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] #Nil))))))]) ## (type: Cursor @@ -276,9 +275,9 @@ (#Cons [[dummy-cursor (+7 ["lux" "doc"])] [dummy-cursor (+5 "Cursors are for specifying the location of Code nodes in Lux files during compilation.")]] (#Cons [[dummy-cursor (+7 ["lux" "type?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "export?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] #Nil)))))]) ## (type: (Ann m v) @@ -300,9 +299,9 @@ (#Cons [[dummy-cursor (+7 ["lux" "type-args"])] [dummy-cursor (+9 (#Cons [dummy-cursor (+5 "m")] (#Cons [dummy-cursor (+5 "v")] #Nil)))]] (#Cons [[dummy-cursor (+7 ["lux" "type?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "export?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] #Nil))))))]) ## (type: (Code' w) @@ -367,9 +366,9 @@ (#Cons [[dummy-cursor (+7 ["lux" "type-args"])] [dummy-cursor (+9 (#Cons [dummy-cursor (+5 "w")] #Nil))]] (#Cons [[dummy-cursor (+7 ["lux" "type?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] (#Cons [[dummy-cursor (+7 ["lux" "export?"])] - [dummy-cursor (+0 true)]] + [dummy-cursor (+0 #1)]] #Nil)))))]) ## (type: Code @@ -383,9 +382,9 @@ (#Record (#Cons [[dummy-cursor (#Tag ["lux" "doc"])] [dummy-cursor (#Text "The type of Code nodes for Lux syntax.")]] (#Cons [[dummy-cursor (#Tag ["lux" "type?"])] - [dummy-cursor (#Bit true)]] + [dummy-cursor (#Bit #1)]] (#Cons [[dummy-cursor (#Tag ["lux" "export?"])] - [dummy-cursor (#Bit true)]] + [dummy-cursor (#Bit #1)]] #Nil))))]) ("lux def" _ann @@ -459,16 +458,16 @@ ("lux def" default-def-meta-exported ("lux check" (#Apply (#Product Code Code) List) (#Cons [(tag$ ["lux" "type?"]) - (bit$ true)] + (bit$ #1)] (#Cons [(tag$ ["lux" "export?"]) - (bit$ true)] + (bit$ #1)] #Nil))) (record$ #Nil)) ("lux def" default-def-meta-unexported ("lux check" (#Apply (#Product Code Code) List) (#Cons [(tag$ ["lux" "type?"]) - (bit$ true)] + (bit$ #1)] #Nil)) (record$ #Nil)) @@ -808,7 +807,7 @@ ("lux def" default-macro-meta ("lux check" (#Apply (#Product Code Code) List) (#Cons [(tag$ ["lux" "macro?"]) - (bit$ true)] + (bit$ #1)] #Nil)) (record$ #Nil)) @@ -878,13 +877,13 @@ ("lux check" (#Function Text Code) ([_ tag] (tuple$ (#Cons [(meta-code ["lux" "Tag"] (tuple$ (#Cons (text$ "lux") (#Cons (text$ tag) #Nil)))) - (#Cons [(meta-code ["lux" "Bit"] (bit$ true)) + (#Cons [(meta-code ["lux" "Bit"] (bit$ #1)) #Nil])])))) (record$ #Nil)) ("lux def" export-meta ("lux check" (#Product Code Code) - [(tag$ ["lux" "export?"]) (bit$ true)]) + [(tag$ ["lux" "export?"]) (bit$ #1)]) (record$ #Nil)) ("lux def" export?-meta @@ -1090,10 +1089,10 @@ #None (#Cons [k v] env') - ({true + ({#1 (#Some v) - false + #0 (get-rep key env')} (text/= k key))} env)) @@ -1246,13 +1245,13 @@ (update-parameters body')) #Nil)))))) body names) - (return (#Cons ({[true _] + (return (#Cons ({[#1 _] body' [_ #Nil] body' - [false _] + [#0 _] (replace-syntax (#Cons [self-name (make-parameter (n/* +2 (n/- +1 (list/size names))))] #Nil) body')} @@ -1293,13 +1292,13 @@ (update-parameters body')) #Nil)))))) body names) - (return (#Cons ({[true _] + (return (#Cons ({[#1 _] body' [_ #Nil] body' - [false _] + [#0 _] (replace-syntax (#Cons [self-name (make-parameter (n/* +2 (n/- +1 (list/size names))))] #Nil) body')} @@ -1508,11 +1507,11 @@ (All [a] (-> (-> a Bit) ($' List a) Bit)) ({#Nil - false + #0 (#Cons x xs') - ({true true - false (any? p xs')} + ({#1 #1 + #0 (any? p xs')} (p x))} xs)) @@ -1718,14 +1717,14 @@ (list [(tag$ ["lux" "doc"]) (text$ "Picks which expression to evaluate based on a bit test value. - (if true + (if #1 \"Oh, yeah!\" \"Aw hell naw!\") => \"Oh, yeah!\"")]) ({(#Cons test (#Cons then (#Cons else #Nil))) - (return (list (form$ (list (record$ (list [(bit$ true) then] - [(bit$ false) else])) + (return (list (form$ (list (record$ (list [(bit$ #1) then] + [(bit$ #0) else])) test)))) _ @@ -1786,7 +1785,7 @@ ({[_ (#Record def-meta)] ({(#Cons [key value] def-meta') ({[_ (#Tag [prefix' name'])] - ({[true true] + ({[#1 #1] (#Some value) _ @@ -1834,7 +1833,7 @@ (def:''' (splice replace? untemplate elems) #Nil (-> Bit (-> Code ($' Meta Code)) ($' List Code) ($' Meta Code)) - ({true + ({#1 ({#Nil (return (tag$ ["lux" "Nil"])) @@ -1865,7 +1864,7 @@ lastO inits))} (list/reverse elems)) - false + #0 (do Monad [=elems (monad/map Monad untemplate elems)] (wrap (untemplate-list =elems)))} @@ -1897,10 +1896,10 @@ [_ [_ (#Text value)]] (return (wrap-meta (form$ (list (tag$ ["lux" "Text"]) (text$ value))))) - [false [_ (#Tag [module name])]] + [#0 [_ (#Tag [module name])]] (return (wrap-meta (form$ (list (tag$ ["lux" "Tag"]) (tuple$ (list (text$ module) (text$ name))))))) - [true [_ (#Tag [module name])]] + [#1 [_ (#Tag [module name])]] (let' [module' ({"" subst @@ -1909,7 +1908,7 @@ module)] (return (wrap-meta (form$ (list (tag$ ["lux" "Tag"]) (tuple$ (list (text$ module') (text$ name)))))))) - [true [_ (#Symbol [module name])]] + [#1 [_ (#Symbol [module name])]] (do Monad [real-name ({"" (if (text/= "" subst) @@ -1922,13 +1921,13 @@ #let [[module name] real-name]] (return (wrap-meta (form$ (list (tag$ ["lux" "Symbol"]) (tuple$ (list (text$ module) (text$ name)))))))) - [false [_ (#Symbol [module name])]] + [#0 [_ (#Symbol [module name])]] (return (wrap-meta (form$ (list (tag$ ["lux" "Symbol"]) (tuple$ (list (text$ module) (text$ name))))))) - [true [_ (#Form (#Cons [[_ (#Symbol ["" "~"])] (#Cons [unquoted #Nil])]))]] + [#1 [_ (#Form (#Cons [[_ (#Symbol ["" "~"])] (#Cons [unquoted #Nil])]))]] (return unquoted) - [true [_ (#Form (#Cons [[_ (#Symbol ["" "~!"])] (#Cons [dependent #Nil])]))]] + [#1 [_ (#Form (#Cons [[_ (#Symbol ["" "~!"])] (#Cons [dependent #Nil])]))]] (do Monad [independent (untemplate replace? subst dependent)] (wrap (wrap-meta (form$ (list (tag$ ["lux" "Form"]) @@ -1936,8 +1935,8 @@ (untemplate-text subst) independent))))))) - [true [_ (#Form (#Cons [[_ (#Symbol ["" "~'"])] (#Cons [keep-quoted #Nil])]))]] - (untemplate false subst keep-quoted) + [#1 [_ (#Form (#Cons [[_ (#Symbol ["" "~'"])] (#Cons [keep-quoted #Nil])]))]] + (untemplate #0 subst keep-quoted) [_ [meta (#Form elems)]] (do Monad @@ -2006,7 +2005,7 @@ ({(#Cons template #Nil) (do Monad [current-module current-module-name - =template (untemplate true current-module template)] + =template (untemplate #1 current-module template)] (wrap (list (form$ (list (text$ "lux check") (symbol$ ["lux" "Code"]) =template))))) @@ -2023,7 +2022,7 @@ (~ body))))")]) ({(#Cons template #Nil) (do Monad - [=template (untemplate true "" template)] + [=template (untemplate #1 "" template)] (wrap (list (form$ (list (text$ "lux check") (symbol$ ["lux" "Code"]) =template))))) _ @@ -2036,7 +2035,7 @@ (' \"YOLO\")")]) ({(#Cons template #Nil) (do Monad - [=template (untemplate false "" template)] + [=template (untemplate #0 "" template)] (wrap (list (form$ (list (text$ "lux check") (symbol$ ["lux" "Code"]) =template))))) _ @@ -2189,7 +2188,7 @@ #Nil (All [a] (-> (-> a Bit) ($' List a) Bit)) - (list/fold (function' [_2 _1] (if _1 (p _2) false)) true xs)) + (list/fold (function' [_2 _1] (if _1 (p _2) #0)) #1 xs)) (def:''' #export (n/= test subject) (list [(tag$ ["lux" "doc"]) @@ -2221,19 +2220,19 @@ (let' [testH (high-bits test) subjectH (high-bits subject)] (if ("lux int <" subjectH testH) - true + #1 (if ("lux i64 =" testH subjectH) ("lux int <" (low-bits subject) (low-bits test)) - false)))) + #0)))) (def:''' #export (n/<= test subject) (list [(tag$ ["lux" "doc"]) (text$ "Nat(ural) less-than-equal.")]) (-> Nat Nat Bit) (if (n/< test subject) - true + #1 ("lux i64 =" test subject))) (def:''' #export (n/> test subject) @@ -2247,7 +2246,7 @@ (text$ "Nat(ural) greater-than-equal.")]) (-> Nat Nat Bit) (if (n/< subject test) - true + #1 ("lux i64 =" test subject))) (macro:' #export (do-template tokens) @@ -2300,7 +2299,7 @@ (-> Rev Rev Bit) (if (n/< ("lux coerce" Nat test) ("lux coerce" Nat subject)) - true + #1 ("lux i64 =" test subject))) (def:''' #export (r/> test subject) @@ -2314,7 +2313,7 @@ (text$ "Rev(olution) greater-than-equal.")]) (-> Rev Rev Bit) (if (r/< subject test) - true + #1 ("lux i64 =" test subject))) (do-template [ @@ -2337,7 +2336,7 @@ (text$ <<=-doc>)]) (-> Bit) (if ( subject test) - true + #1 ( subject test))) (def:''' #export ( test subject) @@ -2351,7 +2350,7 @@ (text$ <>=-doc>)]) (-> Bit) (if ( test subject) - true + #1 ( subject test)))] [ Int "lux i64 =" "lux int <" i/= i/< i/<= i/> i/>= @@ -2539,7 +2538,7 @@ (def:''' (bit/encode x) #Nil (-> Bit Text) - (if x "true" "false")) + (if x "#1" "#0")) (def:''' (digit-to-text digit) #Nil @@ -2607,11 +2606,11 @@ (list [(tag$ ["lux" "doc"]) (text$ "## Bit negation. - (not true) => false + (not #1) => #0 - (not false) => true")]) + (not #0) => #1")]) (-> Bit Bit) - (if x false true)) + (if x #0 #1)) (def:''' (find-macro' modules current-module module name) #Nil @@ -2623,8 +2622,8 @@ gdef (let' [{#module-hash _ #module-aliases _ #definitions bindings #imports _ #tags tags #types types #module-annotations _ #module-state _} ("lux check" Module $module)] (get name bindings))] (let' [[def-type def-meta def-value] ("lux check" Definition gdef)] - ({(#Some [_ (#Bit true)]) - ({(#Some [_ (#Bit true)]) + ({(#Some [_ (#Bit #1)]) + ({(#Some [_ (#Bit #1)]) (#Some ("lux coerce" Macro def-value)) _ @@ -2676,8 +2675,8 @@ (do Monad [ident (normalize ident) output (find-macro ident)] - (wrap ({(#Some _) true - #None false} + (wrap ({(#Some _) #1 + #None #0} output)))) (def:''' (list/join xs) @@ -2859,8 +2858,8 @@ (def:''' (empty? xs) #Nil (All [a] (-> ($' List a) Bit)) - ({#Nil true - _ false} + ({#Nil #1 + _ #0} xs)) (do-template [ ] @@ -2979,10 +2978,10 @@ (macro:' (def:' tokens) (let' [[export? tokens'] ({(#Cons [_ (#Tag ["" "export"])] tokens') - [true tokens'] + [#1 tokens'] _ - [false tokens]} + [#0 tokens]} tokens) parts (: (Maybe [Code (List Code) (Maybe Code) Code]) ({(#Cons [_ (#Form (#Cons name args))] (#Cons type (#Cons body #Nil))) @@ -3174,10 +3173,10 @@ (-> Weekday Bit) (case day (^or #Saturday #Sunday) - true + #1 _ - false))")]) + #0))")]) (case tokens (^ (list& [_ (#Form patterns)] body branches)) (case patterns @@ -3196,10 +3195,10 @@ (-> Code Bit) (case code [_ (#Symbol _)] - true + #1 _ - false)) + #0)) (macro:' #export (let tokens) (list [(tag$ ["lux" "doc"]) @@ -3333,10 +3332,10 @@ (-> (List Code) [Bit (List Code)]) (case tokens (#Cons [_ (#Tag [_ "export"])] tokens') - [true tokens'] + [#1 tokens'] _ - [false tokens])) + [#0 tokens])) (def:' (export ?) (-> Bit (List Code)) @@ -3466,7 +3465,7 @@ _ (` ((~ name) (~+ args))))] (return (list (` (..def: (~+ (export exported?)) (~ def-sig) - (~ (meta-code-merge (` {#.macro? true}) + (~ (meta-code-merge (` {#.macro? #1}) meta)) ..Macro @@ -3528,7 +3527,7 @@ (function (_ [m-name m-type]) [(tag$ ["" m-name]) m-type])) members)) - sig-meta (meta-code-merge (` {#.sig? true}) + sig-meta (meta-code-merge (` {#.sig? #1}) meta) usage (case args #Nil @@ -3569,8 +3568,8 @@ _ (fail )))] - [and (if (~ pre) (~ post) false) "'and' requires >=1 clauses." "Short-circuiting \"and\".\n(and true false true) ## => false"] - [or (if (~ pre) true (~ post)) "'or' requires >=1 clauses." "Short-circuiting \"or\".\n(or true false true) ## => true"]) + [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"]) (def: (index-of part text) (-> Text Text (Maybe Nat)) @@ -3952,7 +3951,7 @@ _ (` ((~ name) (~+ args))))] (return (list (` (..def: (~+ (export exported?)) (~ usage) - (~ (meta-code-merge (` {#.struct? true}) + (~ (meta-code-merge (` {#.struct? #1}) meta)) (~ type) (structure (~+ definitions))))))) @@ -3978,10 +3977,10 @@ (let [[exported? tokens'] (export^ tokens) [rec? tokens'] (case tokens' (#Cons [_ (#Tag [_ "rec"])] tokens') - [true tokens'] + [#1 tokens'] _ - [false tokens']) + [#0 tokens']) parts (: (Maybe [Text (List Code) Code (List Code)]) (case tokens' (^ (list [_ (#Symbol "" name)] [meta-cursor (#Record meta-parts)] [type-cursor (#Record type-parts)])) @@ -4015,10 +4014,10 @@ (case tags?? (#Some tags) (` {#.tags [(~+ (list/map text$ tags))] - #.type? true}) + #.type? #1}) _ - (` {#.type? true}))) + (` {#.type? #1}))) type' (: (Maybe Code) (if rec? (if (empty? args) @@ -4038,7 +4037,7 @@ (#Some type'') (return (list (` (..def: (~+ (export exported?)) (~ type-name) (~ ($_ meta-code-merge (with-type-args args) - (if rec? (' {#.type-rec? true}) (' {})) + (if rec? (' {#.type-rec? #1}) (' {})) type-meta meta)) Type @@ -4236,7 +4235,7 @@ #let [[referral extra] referral+extra] openings+extra (parse-openings extra) #let [[openings extra] openings+extra] - sub-imports (parse-imports true import-name extra)] + sub-imports (parse-imports #1 import-name extra)] (wrap (list& {#import-name import-name #import-alias (#Some (replace-all "." m-name alias)) #import-refer {#refer-defs referral @@ -4250,7 +4249,7 @@ #let [[referral extra] referral+extra] openings+extra (parse-openings extra) #let [[openings extra] openings+extra] - sub-imports (parse-imports true import-name extra)] + sub-imports (parse-imports #1 import-name extra)] (wrap (case [referral openings] [#Nothing #Nil] sub-imports _ (list& {#import-name import-name @@ -4280,7 +4279,7 @@ (List Text)) (function (_ [name [def-type def-meta def-value]]) (case (get-meta ["lux" "export?"] def-meta) - (#Some [_ (#Bit true)]) + (#Some [_ (#Bit #1)]) (list name) _ @@ -4309,7 +4308,7 @@ (let [output (list/fold (function (_ case prev) (or prev (text/= case name))) - false + #0 cases)] output)) @@ -4882,7 +4881,7 @@ _ [(list) tokens]))] current-module current-module-name - imports (parse-imports false current-module _imports) + imports (parse-imports #0 current-module _imports) #let [=imports (list/map (: (-> Importation Code) (function (_ [m-name m-alias =refer]) (` [(~ (text$ m-name)) (~ (text$ (default "" m-alias)))]))) @@ -5523,20 +5522,20 @@ [ (do-template [ ] [(compare ) (compare (:: Code/encode show )) - (compare true (:: Equivalence = ))] - - [(bit true) "true" [_ (#.Bit true)]] - [(bit false) "false" [_ (#.Bit false)]] - [(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"])]] - [(symbol ["yolo" "lol"]) "yolo.lol" [_ (#.Symbol ["yolo" "lol"])]] - [(form (list (bit true) (int 123))) "(true 123)" (^ [_ (#.Form (list [_ (#.Bit true)] [_ (#.Int 123)]))])] - [(tuple (list (bit true) (int 123))) "[true 123]" (^ [_ (#.Tuple (list [_ (#.Bit true)] [_ (#.Int 123)]))])] - [(record (list [(bit true) (int 123)])) "{true 123}" (^ [_ (#.Record (list [[_ (#.Bit true)] [_ (#.Int 123)]]))])] - [(local-tag "lol") "#lol" [_ (#.Tag ["" "lol"])]] - [(local-symbol "lol") "lol" [_ (#.Symbol ["" "lol"])]] + (compare #1 (:: Equivalence = ))] + + [(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"])]] + [(symbol ["yolo" "lol"]) "yolo.lol" [_ (#.Symbol ["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-symbol "lol") "lol" [_ (#.Symbol ["" "lol"])]] )] (test-all ))))} (case tokens @@ -5652,7 +5651,7 @@ (return [expr binding]) _ - (return [level (` true)]) + (return [level (` #1)]) )) (def: (multi-level-case^ levels) @@ -5684,7 +5683,7 @@ "Useful in situations where the result of a branch depends on further refinements on the values being matched." "For example:" (case (split (size static) uri) - (^multi (#.Some [chunk uri']) [(text/= static chunk) true]) + (^multi (#.Some [chunk uri']) [(text/= static chunk) #1]) (match-uri endpoint? parts' uri') _ @@ -6228,3 +6227,12 @@ (nat/encode line) separator (nat/encode column))] ($_ "lux text concat" "[" fields "]"))) + +(do-template [ ] + [(def: #export #0) + (def: #export #1)] + + [false true] + [no yes] + [off on] + ) -- cgit v1.2.3