aboutsummaryrefslogtreecommitdiff
path: root/stdlib/test
diff options
context:
space:
mode:
authorEduardo Julian2018-07-13 22:01:32 -0400
committerEduardo Julian2018-07-13 22:01:32 -0400
commit69fefab57c40f323d759dc444dbcebad15071585 (patch)
treedb08a3ea37c7818c8a98fc995d3c19440141b700 /stdlib/test
parent6acf4ffc362c0f8ef77d96f8cfe991adb2d9a0eb (diff)
Re-named "Bool" type to "Bit".
Diffstat (limited to 'stdlib/test')
-rw-r--r--stdlib/test/test/lux/concurrency/promise.lux2
-rw-r--r--stdlib/test/test/lux/control/exception.lux6
-rw-r--r--stdlib/test/test/lux/control/parser.lux16
-rw-r--r--stdlib/test/test/lux/control/region.lux2
-rw-r--r--stdlib/test/test/lux/control/state.lux2
-rw-r--r--stdlib/test/test/lux/data/bit.lux38
-rw-r--r--stdlib/test/test/lux/data/bool.lux38
-rw-r--r--stdlib/test/test/lux/data/collection/list.lux14
-rw-r--r--stdlib/test/test/lux/data/format/json.lux22
-rw-r--r--stdlib/test/test/lux/data/number/complex.lux4
-rw-r--r--stdlib/test/test/lux/data/number/i64.lux2
-rw-r--r--stdlib/test/test/lux/data/text/lexer.lux8
-rw-r--r--stdlib/test/test/lux/data/text/regex.lux6
-rw-r--r--stdlib/test/test/lux/language/compiler/analysis/case.lux4
-rw-r--r--stdlib/test/test/lux/language/compiler/analysis/function.lux2
-rw-r--r--stdlib/test/test/lux/language/compiler/analysis/primitive.lux4
-rw-r--r--stdlib/test/test/lux/language/compiler/analysis/procedure/common.lux20
-rw-r--r--stdlib/test/test/lux/language/compiler/analysis/reference.lux4
-rw-r--r--stdlib/test/test/lux/language/compiler/analysis/structure.lux16
-rw-r--r--stdlib/test/test/lux/language/compiler/synthesis/case.lux6
-rw-r--r--stdlib/test/test/lux/language/compiler/synthesis/function.lux6
-rw-r--r--stdlib/test/test/lux/language/compiler/synthesis/primitive.lux12
-rw-r--r--stdlib/test/test/lux/language/compiler/synthesis/structure.lux4
-rw-r--r--stdlib/test/test/lux/language/syntax.lux4
-rw-r--r--stdlib/test/test/lux/language/type.lux8
-rw-r--r--stdlib/test/test/lux/language/type/check.lux10
-rw-r--r--stdlib/test/test/lux/macro/code.lux24
-rw-r--r--stdlib/test/test/lux/macro/poly/equivalence.lux10
-rw-r--r--stdlib/test/test/lux/macro/syntax.lux44
-rw-r--r--stdlib/test/test/lux/math.lux22
-rw-r--r--stdlib/test/test/lux/math/logic/fuzzy.lux56
-rw-r--r--stdlib/test/test/lux/math/modular.lux34
-rw-r--r--stdlib/test/test/lux/type/implicit.lux6
-rw-r--r--stdlib/test/test/lux/type/object/protocol.lux6
-rw-r--r--stdlib/test/test/lux/world/blob.lux4
-rw-r--r--stdlib/test/test/lux/world/net/tcp.lux2
36 files changed, 234 insertions, 234 deletions
diff --git a/stdlib/test/test/lux/concurrency/promise.lux b/stdlib/test/test/lux/concurrency/promise.lux
index f0b0bb865..29bab782c 100644
--- a/stdlib/test/test/lux/concurrency/promise.lux
+++ b/stdlib/test/test/lux/concurrency/promise.lux
@@ -61,7 +61,7 @@
(test "Cannot re-resolve a resolved promise."
(and (not (io.run (&.resolve false (&/wrap true))))
- (io.run (&.resolve true (: (&.Promise Bool) (&.promise #.None))))))
+ (io.run (&.resolve true (: (&.Promise Bit) (&.promise #.None))))))
(wrap (do &.Monad<Promise>
[?none (&.time-out +100 (&.delay +200 true))
diff --git a/stdlib/test/test/lux/control/exception.lux b/stdlib/test/test/lux/control/exception.lux
index 85b331620..9e11dbe0f 100644
--- a/stdlib/test/test/lux/control/exception.lux
+++ b/stdlib/test/test/lux/control/exception.lux
@@ -22,9 +22,9 @@
(context: "Exceptions"
(<| (times +100)
(do @
- [should-throw? r.bool
- which? r.bool
- should-catch? r.bool
+ [should-throw? r.bit
+ which? r.bit
+ should-catch? r.bit
default-val r.nat
some-val r.nat
another-val r.nat
diff --git a/stdlib/test/test/lux/control/parser.lux b/stdlib/test/test/lux/control/parser.lux
index a8ec24446..6028eed1a 100644
--- a/stdlib/test/test/lux/control/parser.lux
+++ b/stdlib/test/test/lux/control/parser.lux
@@ -16,13 +16,13 @@
## [Utils]
(def: (should-fail input)
- (All [a] (-> (Error a) Bool))
+ (All [a] (-> (Error a) Bit))
(case input
(#error.Error _) true
_ false))
(def: (enforced? parser input)
- (All [s] (-> (&.Parser s Any) s Bool))
+ (All [s] (-> (&.Parser s Any) s Bit))
(case (&.run input parser)
(#error.Success [_ []])
true
@@ -31,7 +31,7 @@
false))
(def: (found? parser input)
- (All [s] (-> (&.Parser s Bool) s Bool))
+ (All [s] (-> (&.Parser s Bit) s Bit))
(case (&.run input parser)
(#error.Success [_ true])
true
@@ -40,7 +40,7 @@
false))
(def: (fails? input)
- (All [a] (-> (Error a) Bool))
+ (All [a] (-> (Error a) Bit))
(case input
(#error.Error _)
true
@@ -60,9 +60,9 @@
(context: "Assertions"
(test "Can make assertions while parsing."
(and (match []
- (&.run (list (code.bool true) (code.int 123))
+ (&.run (list (code.bit true) (code.int 123))
(&.assert "yolo" true)))
- (fails? (&.run (list (code.bool true) (code.int 123))
+ (fails? (&.run (list (code.bit true) (code.int 123))
(&.assert "yolo" false))))))
(context: "Combinators [Part 1]"
@@ -105,14 +105,14 @@
(match -123
(&.run (list (code.int -123) (code.int 456) (code.int 789))
(&.either positive s.int)))
- (fails? (&.run (list (code.bool true) (code.int 456) (code.int 789))
+ (fails? (&.run (list (code.bit true) (code.int 456) (code.int 789))
(&.either positive s.int))))))
(test "Can create the opposite/negation of any parser."
(and (fails? (&.run (list (code.int 123) (code.int 456) (code.int 789))
(&.not s.int)))
(match []
- (&.run (list (code.bool true) (code.int 456) (code.int 789))
+ (&.run (list (code.bit true) (code.int 456) (code.int 789))
(&.not s.int)))))
))
diff --git a/stdlib/test/test/lux/control/region.lux b/stdlib/test/test/lux/control/region.lux
index 606be66bf..544b42982 100644
--- a/stdlib/test/test/lux/control/region.lux
+++ b/stdlib/test/test/lux/control/region.lux
@@ -18,7 +18,7 @@
(do-template [<name> <success> <error>]
[(def: (<name> result)
- (All [a] (-> (Error a) Bool))
+ (All [a] (-> (Error a) Bit))
(case result
(#e.Success _) <success>
(#e.Error _) <error>))]
diff --git a/stdlib/test/test/lux/control/state.lux b/stdlib/test/test/lux/control/state.lux
index 9f352df48..c39be3197 100644
--- a/stdlib/test/test/lux/control/state.lux
+++ b/stdlib/test/test/lux/control/state.lux
@@ -12,7 +12,7 @@
lux/test)
(def: (with-conditions [state output] computation)
- (-> [Nat Nat] (&.State Nat Nat) Bool)
+ (-> [Nat Nat] (&.State Nat Nat) Bit)
(|> computation
(&.run state)
product.right
diff --git a/stdlib/test/test/lux/data/bit.lux b/stdlib/test/test/lux/data/bit.lux
new file mode 100644
index 000000000..f9ab9551f
--- /dev/null
+++ b/stdlib/test/test/lux/data/bit.lux
@@ -0,0 +1,38 @@
+(.module:
+ [lux #*
+ [control
+ ["M" monad (#+ do Monad)]]
+ [io]
+ [data
+ bit]
+ [math
+ ["r" random]]]
+ lux/test)
+
+(context: "Bit operations."
+ (<| (times +100)
+ (do @
+ [value r.bit]
+ (test "" (and (not (and value (not value)))
+ (or value (not value))
+
+ (not (:: Or@Monoid<Bit> identity))
+ (:: Or@Monoid<Bit> compose value (not value))
+ (:: And@Monoid<Bit> identity)
+ (not (:: And@Monoid<Bit> compose value (not value)))
+
+ (:: Equivalence<Bit> = value (not (not value)))
+ (not (:: Equivalence<Bit> = value (not value)))
+
+ (not (:: Equivalence<Bit> = value ((complement id) value)))
+ (:: Equivalence<Bit> = value ((complement not) value))
+
+ (case (|> value
+ (:: Codec<Text,Bit> encode)
+ (:: Codec<Text,Bit> decode))
+ (#.Right dec-value)
+ (:: Equivalence<Bit> = value dec-value)
+
+ (#.Left _)
+ false)
+ )))))
diff --git a/stdlib/test/test/lux/data/bool.lux b/stdlib/test/test/lux/data/bool.lux
deleted file mode 100644
index 0413c2632..000000000
--- a/stdlib/test/test/lux/data/bool.lux
+++ /dev/null
@@ -1,38 +0,0 @@
-(.module:
- [lux #*
- [control
- ["M" monad (#+ do Monad)]]
- [io]
- [data
- bool]
- [math
- ["r" random]]]
- lux/test)
-
-(context: "Boolean operations."
- (<| (times +100)
- (do @
- [value r.bool]
- (test "" (and (not (and value (not value)))
- (or value (not value))
-
- (not (:: Or@Monoid<Bool> identity))
- (:: Or@Monoid<Bool> compose value (not value))
- (:: And@Monoid<Bool> identity)
- (not (:: And@Monoid<Bool> compose value (not value)))
-
- (:: Equivalence<Bool> = value (not (not value)))
- (not (:: Equivalence<Bool> = value (not value)))
-
- (not (:: Equivalence<Bool> = value ((complement id) value)))
- (:: Equivalence<Bool> = value ((complement not) value))
-
- (case (|> value
- (:: Codec<Text,Bool> encode)
- (:: Codec<Text,Bool> decode))
- (#.Right dec-value)
- (:: Equivalence<Bool> = value dec-value)
-
- (#.Left _)
- false)
- )))))
diff --git a/stdlib/test/test/lux/data/collection/list.lux b/stdlib/test/test/lux/data/collection/list.lux
index f7e73ef9b..0945a9abb 100644
--- a/stdlib/test/test/lux/data/collection/list.lux
+++ b/stdlib/test/test/lux/data/collection/list.lux
@@ -5,7 +5,7 @@
[monad (#+ do Monad)]
pipe]
[data [number]
- [bool]
+ [bit]
[product]
[maybe]
[collection
@@ -48,7 +48,7 @@
(test "Filtering by a predicate and its complement should result in a number of elements equal to the original list."
(and (n/= (&.size sample)
(n/+ (&.size (&.filter n/even? sample))
- (&.size (&.filter (bool.complement n/even?) sample))))
+ (&.size (&.filter (bit.complement n/even?) sample))))
(let [[plus minus] (&.partition n/even? sample)]
(n/= (&.size sample)
(n/+ (&.size plus)
@@ -56,9 +56,9 @@
(test "If every element in a list satisfies a predicate, there can't be any that satisfy its complement."
(if (&.every? n/even? sample)
- (and (not (&.any? (bool.complement n/even?) sample))
- (&.empty? (&.filter (bool.complement n/even?) sample)))
- (&.any? (bool.complement n/even?) sample)))
+ (and (not (&.any? (bit.complement n/even?) sample))
+ (&.empty? (&.filter (bit.complement n/even?) sample)))
+ (&.any? (bit.complement n/even?) sample)))
(test "Any element of the list can be considered its member."
(let [elem (maybe.assume (&.nth idx sample))]
@@ -196,11 +196,11 @@
(#.Some found)
(and (n/even? found)
(&.any? n/even? sample)
- (not (&.every? (bool.complement n/even?) sample)))
+ (not (&.every? (bit.complement n/even?) sample)))
#.None
(and (not (&.any? n/even? sample))
- (&.every? (bool.complement n/even?) sample))))
+ (&.every? (bit.complement n/even?) sample))))
(test "You can iteratively construct a list, generating values until you're done."
(= (&.n/range +0 (dec size))
diff --git a/stdlib/test/test/lux/data/format/json.lux b/stdlib/test/test/lux/data/format/json.lux
index e3b3c6f66..f648dce28 100644
--- a/stdlib/test/test/lux/data/format/json.lux
+++ b/stdlib/test/test/lux/data/format/json.lux
@@ -9,7 +9,7 @@
["p" parser]]
[data
["e" error]
- [bool]
+ [bit]
[maybe]
[number]
["." text
@@ -50,7 +50,7 @@
[size (:: @ map (n/% +2) r.nat)]
($_ r.alt
(:: @ wrap [])
- r.bool
+ r.bit
(|> r.frac (:: @ map (f/* 1_000_000.0)))
(r.unicode size)
(r.row size gen-json)
@@ -77,7 +77,7 @@
))))
(type: Variant
- (#Case0 Bool)
+ (#Case0 Bit)
(#Case1 Text)
(#Case2 Frac))
@@ -86,14 +86,14 @@
(#Addition Frac Recursive))
(type: Record
- {#bool Bool
+ {#bit Bit
#frac Frac
#text Text
#maybe (Maybe Frac)
#list (List Frac)
#dict (d.Dictionary Text Frac)
## #variant Variant
- ## #tuple [Bool Frac Text]
+ ## #tuple [Bit Frac Text]
#recursive Recursive
## #instant ti.Instant
#duration tdu.Duration
@@ -118,14 +118,14 @@
(do r.Monad<Random>
[size (:: @ map (n/% +2) r.nat)]
($_ r.seq
- r.bool
+ r.bit
r.frac
(r.unicode size)
(r.maybe r.frac)
(r.list size r.frac)
(r.dictionary text.Hash<Text> size (r.unicode size) r.frac)
- ## ($_ r.alt r.bool (r.unicode size) r.frac)
- ## ($_ r.seq r.bool r.frac (r.unicode size))
+ ## ($_ r.alt r.bit (r.unicode size) r.frac)
+ ## ($_ r.seq r.bit r.frac (r.unicode size))
gen-recursive
## _instant.instant
_duration.duration
@@ -140,7 +140,7 @@
(let [variant/= (function (_ left right)
(case [left right]
[(#Case0 left') (#Case0 right')]
- (:: bool.Equivalence<Bool> = left' right')
+ (:: bit.Equivalence<Bit> = left' right')
[(#Case1 left') (#Case1 right')]
(:: text.Equivalence<Text> = left' right')
@@ -150,7 +150,7 @@
_
false))]
- (and (:: bool.Equivalence<Bool> = (get@ #bool recL) (get@ #bool recR))
+ (and (:: bit.Equivalence<Bit> = (get@ #bit recL) (get@ #bit recR))
(f/= (get@ #frac recL) (get@ #frac recR))
(:: text.Equivalence<Text> = (get@ #text recL) (get@ #text recR))
(:: (maybe.Equivalence<Maybe> number.Equivalence<Frac>) = (get@ #maybe recL) (get@ #maybe recR))
@@ -159,7 +159,7 @@
## (variant/= (get@ #variant recL) (get@ #variant recR))
## (let [[tL0 tL1 tL2] (get@ #tuple recL)
## [tR0 tR1 tR2] (get@ #tuple recR)]
- ## (and (:: bool.Equivalence<Bool> = tL0 tR0)
+ ## (and (:: bit.Equivalence<Bit> = tL0 tR0)
## (f/= tL1 tR1)
## (:: text.Equivalence<Text> = tL2 tR2)))
(:: Equivalence<Recursive> = (get@ #recursive recL) (get@ #recursive recR))
diff --git a/stdlib/test/test/lux/data/number/complex.lux b/stdlib/test/test/lux/data/number/complex.lux
index 03ec307ff..15d759ba7 100644
--- a/stdlib/test/test/lux/data/number/complex.lux
+++ b/stdlib/test/test/lux/data/number/complex.lux
@@ -19,7 +19,7 @@
(def: margin-of-error Frac 1.0e-9)
(def: (within? margin standard value)
- (-> Frac &.Complex &.Complex Bool)
+ (-> Frac &.Complex &.Complex Bit)
(let [real-dist (frac/abs (f/- (get@ #&.real standard)
(get@ #&.real value)))
imgn-dist (frac/abs (f/- (get@ #&.imaginary standard)
@@ -161,7 +161,7 @@
))))
(def: (trigonometric-symmetry forward backward angle)
- (-> (-> &.Complex &.Complex) (-> &.Complex &.Complex) &.Complex Bool)
+ (-> (-> &.Complex &.Complex) (-> &.Complex &.Complex) &.Complex Bit)
(let [normal (|> angle forward backward)]
(|> normal forward backward (within? margin-of-error normal))))
diff --git a/stdlib/test/test/lux/data/number/i64.lux b/stdlib/test/test/lux/data/number/i64.lux
index 1dd9dd314..52b80ea25 100644
--- a/stdlib/test/test/lux/data/number/i64.lux
+++ b/stdlib/test/test/lux/data/number/i64.lux
@@ -39,7 +39,7 @@
(n/= &.width
(n/+ (&.count pattern)
(&.count (&.not pattern)))))
- (test "Can do simple binary boolean logic."
+ (test "Can do simple binary logic."
(and (n/= +0
(&.and pattern
(&.not pattern)))
diff --git a/stdlib/test/test/lux/data/text/lexer.lux b/stdlib/test/test/lux/data/text/lexer.lux
index 25abe3ae4..b02082357 100644
--- a/stdlib/test/test/lux/data/text/lexer.lux
+++ b/stdlib/test/test/lux/data/text/lexer.lux
@@ -18,13 +18,13 @@
## [Utils]
(def: (should-fail input)
- (All [a] (-> (E.Error a) Bool))
+ (All [a] (-> (E.Error a) Bit))
(case input
(#.Left _) true
_ false))
(def: (should-passT test input)
- (-> Text (E.Error Text) Bool)
+ (-> Text (E.Error Text) Bit)
(case input
(#.Right output)
(text/= test output)
@@ -33,7 +33,7 @@
false))
(def: (should-passL test input)
- (-> (List Text) (E.Error (List Text)) Bool)
+ (-> (List Text) (E.Error (List Text)) Bit)
(let [(^open "list/") (list.Equivalence<List> text.Equivalence<Text>)]
(case input
(#.Right output)
@@ -43,7 +43,7 @@
false)))
(def: (should-passE test input)
- (-> (Either Text Text) (E.Error (Either Text Text)) Bool)
+ (-> (Either Text Text) (E.Error (Either Text Text)) Bit)
(case input
(#.Right output)
(case [test output]
diff --git a/stdlib/test/test/lux/data/text/regex.lux b/stdlib/test/test/lux/data/text/regex.lux
index 16970af9c..ff09a55db 100644
--- a/stdlib/test/test/lux/data/text/regex.lux
+++ b/stdlib/test/test/lux/data/text/regex.lux
@@ -20,7 +20,7 @@
## [Utils]
(def: (should-pass regex input)
- (-> (lexer.Lexer Text) Text Bool)
+ (-> (lexer.Lexer Text) Text Bit)
(|> (lexer.run input regex)
(case> (#.Right parsed)
(text/= parsed input)
@@ -29,7 +29,7 @@
false)))
(def: (should-passT test regex input)
- (-> Text (lexer.Lexer Text) Text Bool)
+ (-> Text (lexer.Lexer Text) Text Bit)
(|> (lexer.run input regex)
(case> (#.Right parsed)
(text/= test parsed)
@@ -38,7 +38,7 @@
false)))
(def: (should-fail regex input)
- (All [a] (-> (lexer.Lexer a) Text Bool))
+ (All [a] (-> (lexer.Lexer a) Text Bit))
(|> (lexer.run input regex)
(case> (#.Left _) true _ false)))
diff --git a/stdlib/test/test/lux/language/compiler/analysis/case.lux b/stdlib/test/test/lux/language/compiler/analysis/case.lux
index 4e01ae3bd..14b762271 100644
--- a/stdlib/test/test/lux/language/compiler/analysis/case.lux
+++ b/stdlib/test/test/lux/language/compiler/analysis/case.lux
@@ -44,9 +44,9 @@
(wrap (#.Cons head tail+)))))
(def: #export (exhaustive-branches allow-literals? variantTC inputC)
- (-> Bool (List [Code Code]) Code (r.Random (List Code)))
+ (-> Bit (List [Code Code]) Code (r.Random (List Code)))
(case inputC
- [_ (#.Bool _)]
+ [_ (#.Bit _)]
(random/wrap (list (' true) (' false)))
(^template [<tag> <gen> <wrapper>]
diff --git a/stdlib/test/test/lux/language/compiler/analysis/function.lux b/stdlib/test/test/lux/language/compiler/analysis/function.lux
index 1edbfd949..32ef59e3f 100644
--- a/stdlib/test/test/lux/language/compiler/analysis/function.lux
+++ b/stdlib/test/test/lux/language/compiler/analysis/function.lux
@@ -35,7 +35,7 @@
(def: analyse (expression.analyser (:coerce language.Eval [])))
(def: (check-apply expectedT num-args analysis)
- (-> Type Nat (Operation Analysis) Bool)
+ (-> Type Nat (Operation Analysis) Bit)
(|> analysis
(typeA.with-type expectedT)
(compiler.run [analysisE.bundle (init.compiler [])])
diff --git a/stdlib/test/test/lux/language/compiler/analysis/primitive.lux b/stdlib/test/test/lux/language/compiler/analysis/primitive.lux
index 8cd764b00..fadde9bb0 100644
--- a/stdlib/test/test/lux/language/compiler/analysis/primitive.lux
+++ b/stdlib/test/test/lux/language/compiler/analysis/primitive.lux
@@ -36,7 +36,7 @@
[(r.seq (random/wrap <type>) (random/map <code-wrapper> <value-gen>))]
[Any code.tuple (r.list +0 ..unit)]
- [Bool code.bool r.bool]
+ [Bit code.bit r.bit]
[Nat code.nat r.nat]
[Int code.int r.int]
[Rev code.rev r.rev]
@@ -83,7 +83,7 @@
_
false))))]
- ["bool" Bool #analysis.Bool r.bool code.bool]
+ ["bit" Bit #analysis.Bit r.bit code.bit]
["nat" Nat #analysis.Nat r.nat code.nat]
["int" Int #analysis.Int r.int code.int]
["rev" Rev #analysis.Rev r.rev code.rev]
diff --git a/stdlib/test/test/lux/language/compiler/analysis/procedure/common.lux b/stdlib/test/test/lux/language/compiler/analysis/procedure/common.lux
index e3b8cc9b5..7ea4a23bd 100644
--- a/stdlib/test/test/lux/language/compiler/analysis/procedure/common.lux
+++ b/stdlib/test/test/lux/language/compiler/analysis/procedure/common.lux
@@ -30,7 +30,7 @@
(do-template [<name> <success> <failure>]
[(def: (<name> procedure params output-type)
- (-> Text (List Code) Type Bool)
+ (-> Text (List Code) Type Bit)
(|> (scope.with-scope ""
(typeA.with-type output-type
(_primitive.analyse (` ((~ (code.text procedure)) (~+ params))))))
@@ -53,9 +53,9 @@
(r.filter (|>> product.left (type/= primT) not)))]
($_ seq
(test "Can test for reference equality."
- (check-success+ "lux is" (list primC primC) Bool))
+ (check-success+ "lux is" (list primC primC) Bit))
(test "Reference equality must be done with elements of the same type."
- (check-failure+ "lux is" (list primC antiC) Bool))
+ (check-failure+ "lux is" (list primC antiC) Bit))
(test "Can 'try' risky IO computations."
(check-success+ "lux try"
(list (` ([(~' _) (~' _)] (~ primC))))
@@ -100,9 +100,9 @@
(test "Can calculate remainder of integers."
(check-success+ "lux int %" (list subjectC paramC) Int))
(test "Can test equivalence of integers."
- (check-success+ "lux int =" (list subjectC paramC) Bool))
+ (check-success+ "lux int =" (list subjectC paramC) Bit))
(test "Can compare integers."
- (check-success+ "lux int <" (list subjectC paramC) Bool))
+ (check-success+ "lux int <" (list subjectC paramC) Bit))
(test "Can convert integer to fraction."
(check-success+ "lux int to-frac" (list subjectC) Frac))
(test "Can convert integer to text."
@@ -127,9 +127,9 @@
(test "Can calculate remainder of frac numbers."
(check-success+ "lux frac %" (list subjectC paramC) Frac))
(test "Can test equivalence of frac numbers."
- (check-success+ "lux frac =" (list subjectC paramC) Bool))
+ (check-success+ "lux frac =" (list subjectC paramC) Bit))
(test "Can compare frac numbers."
- (check-success+ "lux frac <" (list subjectC paramC) Bool))
+ (check-success+ "lux frac <" (list subjectC paramC) Bit))
(test "Can obtain minimum frac number."
(check-success+ "lux frac min" (list) Frac))
(test "Can obtain maximum frac number."
@@ -154,9 +154,9 @@
toC (|> r.nat (:: @ map code.nat))]
($_ seq
(test "Can test text equivalence."
- (check-success+ "lux text =" (list subjectC paramC) Bool))
+ (check-success+ "lux text =" (list subjectC paramC) Bit))
(test "Compare texts in lexicographical order."
- (check-success+ "lux text <" (list subjectC paramC) Bool))
+ (check-success+ "lux text <" (list subjectC paramC) Bit))
(test "Can concatenate one text to another."
(check-success+ "lux text concat" (list subjectC paramC) Text))
(test "Can find the index of a piece of text inside a larger one that (may) contain it."
@@ -262,7 +262,7 @@
(test "Can swap the value of an atomic reference."
(|> (scope.with-scope ""
(scope.with-local [var-name atomT]
- (typeA.with-type Bool
+ (typeA.with-type Bit
(_primitive.analyse (` ("lux atom compare-and-swap"
(~ (code.symbol ["" var-name]))
(~ elemC)
diff --git a/stdlib/test/test/lux/language/compiler/analysis/reference.lux b/stdlib/test/test/lux/language/compiler/analysis/reference.lux
index 00ab606a3..d68e2e8f4 100644
--- a/stdlib/test/test/lux/language/compiler/analysis/reference.lux
+++ b/stdlib/test/test/lux/language/compiler/analysis/reference.lux
@@ -31,7 +31,7 @@
(def: analyse (expression.analyser (:coerce language.Eval [])))
-(type: Check (-> (e.Error Any) Bool))
+(type: Check (-> (e.Error Any) Bit))
(do-template [<name> <on-success> <on-failure>]
[(def: <name>
@@ -47,7 +47,7 @@
)
(def: (reach-test var-name [export? def-module] [import? dependent-module] check!)
- (-> Text [Bool Text] [Bool Text] Check Bool)
+ (-> Text [Bit Text] [Bit Text] Check Bit)
(|> (do compiler.Monad<Operation>
[_ (module.with-module +0 def-module
(module.define var-name [Any
diff --git a/stdlib/test/test/lux/language/compiler/analysis/structure.lux b/stdlib/test/test/lux/language/compiler/analysis/structure.lux
index 664e6e29f..8d8ce4cd0 100644
--- a/stdlib/test/test/lux/language/compiler/analysis/structure.lux
+++ b/stdlib/test/test/lux/language/compiler/analysis/structure.lux
@@ -4,7 +4,7 @@
[monad (#+ do)]
pipe]
[data
- [bool ("bool/" Equivalence<Bool>)]
+ [bit ("bit/" Equivalence<Bit>)]
["e" error]
[product]
[maybe]
@@ -36,7 +36,7 @@
(do-template [<name> <on-success> <on-error>]
[(def: #export <name>
- (All [a] (-> (Operation a) Bool))
+ (All [a] (-> (Operation a) Bit))
(|>> (compiler.run [analysisE.bundle (init.compiler [])])
(case> (#e.Success _)
<on-success>
@@ -49,16 +49,16 @@
)
(def: (check-sum' size tag variant)
- (-> Nat Tag (Variant Analysis) Bool)
+ (-> Nat Tag (Variant Analysis) Bit)
(let [variant-tag (if (get@ #analysis.right? variant)
(inc (get@ #analysis.lefts variant))
(get@ #analysis.lefts variant))]
(|> size dec (n/= tag)
- (bool/= (get@ #analysis.right? variant))
+ (bit/= (get@ #analysis.right? variant))
(and (n/= tag variant-tag)))))
(def: (check-sum type size tag analysis)
- (-> Type Nat Tag (Operation Analysis) Bool)
+ (-> Type Nat Tag (Operation Analysis) Bit)
(|> analysis
(typeA.with-type type)
(compiler.run [analysisE.bundle (init.compiler [])])
@@ -77,7 +77,7 @@
(module.with-module +0 module)))
(def: (check-variant module tags type size tag analysis)
- (-> Text (List module.Tag) Type Nat Tag (Operation Analysis) Bool)
+ (-> Text (List module.Tag) Type Nat Tag (Operation Analysis) Bit)
(|> analysis
(tagged module tags type)
(typeA.with-type type)
@@ -91,11 +91,11 @@
false)))
(def: (right-size? size)
- (-> Nat (-> Analysis Bool))
+ (-> Nat (-> Analysis Bit))
(|>> analysis.tuple list.size (n/= size)))
(def: (check-record-inference module tags type size analysis)
- (-> Text (List module.Tag) Type Nat (Operation [Type Analysis]) Bool)
+ (-> Text (List module.Tag) Type Nat (Operation [Type Analysis]) Bit)
(|> analysis
(tagged module tags type)
(compiler.run [analysisE.bundle (init.compiler [])])
diff --git a/stdlib/test/test/lux/language/compiler/synthesis/case.lux b/stdlib/test/test/lux/language/compiler/synthesis/case.lux
index 264bc0967..ff84207a1 100644
--- a/stdlib/test/test/lux/language/compiler/synthesis/case.lux
+++ b/stdlib/test/test/lux/language/compiler/synthesis/case.lux
@@ -60,15 +60,15 @@
(context: "If expressions."
(<| (times +100)
(do @
- [then|else r.bool
+ [then|else r.bit
inputA //primitive.primitive
thenA //primitive.primitive
elseA //primitive.primitive
#let [thenB (: Branch
- [(#analysisL.Simple (#analysisL.Bool true))
+ [(#analysisL.Simple (#analysisL.Bit true))
thenA])
elseB (: Branch
- [(#analysisL.Simple (#analysisL.Bool false))
+ [(#analysisL.Simple (#analysisL.Bit false))
elseA])
ifA (if then|else
(analysisL.control/case [inputA [thenB (list elseB)]])
diff --git a/stdlib/test/test/lux/language/compiler/synthesis/function.lux b/stdlib/test/test/lux/language/compiler/synthesis/function.lux
index 51b2a2e17..0116033bd 100644
--- a/stdlib/test/test/lux/language/compiler/synthesis/function.lux
+++ b/stdlib/test/test/lux/language/compiler/synthesis/function.lux
@@ -30,7 +30,7 @@
(r.rec
(function (_ constant-function)
(do r.Monad<Random>
- [function? r.bool]
+ [function? r.bit]
(if function?
(do @
[[arity bodyA predictionA] constant-function]
@@ -62,7 +62,7 @@
(dict.new number.Hash<Nat>))
(list.enumerate current-env))]
(do @
- [nest? r.bool]
+ [nest? r.bit]
(if nest?
(do @
[num-picks (:: @ map (n/max +1) (pick (inc current-env/size)))
@@ -91,7 +91,7 @@
nest? true]
(if nest?
(do r.Monad<Random>
- [nest?' r.bool
+ [nest?' r.bit
[arity' bodyA predictionA] (recur (inc arity) nest?')]
(wrap [arity'
(#analysisL.Function (list) bodyA)
diff --git a/stdlib/test/test/lux/language/compiler/synthesis/primitive.lux b/stdlib/test/test/lux/language/compiler/synthesis/primitive.lux
index 3bea7682d..c804b94ff 100644
--- a/stdlib/test/test/lux/language/compiler/synthesis/primitive.lux
+++ b/stdlib/test/test/lux/language/compiler/synthesis/primitive.lux
@@ -24,7 +24,7 @@
[primitive (: (r.Random analysisL.Primitive)
($_ r.alt
(wrap [])
- r.bool
+ r.bit
r.nat
r.int
r.rev
@@ -33,14 +33,14 @@
(wrap (#analysisL.Primitive primitive))))
(def: #export (corresponds? analysis synthesis)
- (-> Analysis Synthesis Bool)
+ (-> Analysis Synthesis Bit)
(case [synthesis analysis]
[(#//.Primitive (#//.Text valueS))
(#analysisL.Primitive (#analysisL.Unit valueA))]
(is? valueS (:coerce Text valueA))
- [(#//.Primitive (#//.Bool valueS))
- (#analysisL.Primitive (#analysisL.Bool valueA))]
+ [(#//.Primitive (#//.Bit valueS))
+ (#analysisL.Primitive (#analysisL.Bit valueA))]
(is? valueS valueA)
[(#//.Primitive (#//.I64 valueS))
@@ -69,7 +69,7 @@
(context: "Primitives."
(<| (times +100)
(do @
- [%bool% r.bool
+ [%bit% r.bit
%nat% r.nat
%int% r.int
%rev% r.rev
@@ -88,7 +88,7 @@
false)))]
["unit" #analysisL.Unit #//.Text //.unit]
- ["bool" #analysisL.Bool #//.Bool %bool%]
+ ["bit" #analysisL.Bit #//.Bit %bit%]
["nat" #analysisL.Nat #//.I64 (.i64 %nat%)]
["int" #analysisL.Int #//.I64 (.i64 %int%)]
["rev" #analysisL.Rev #//.I64 (.i64 %rev%)]
diff --git a/stdlib/test/test/lux/language/compiler/synthesis/structure.lux b/stdlib/test/test/lux/language/compiler/synthesis/structure.lux
index 0b9f705ff..db56757d1 100644
--- a/stdlib/test/test/lux/language/compiler/synthesis/structure.lux
+++ b/stdlib/test/test/lux/language/compiler/synthesis/structure.lux
@@ -5,7 +5,7 @@
[monad (#+ do)]
pipe]
[data
- [bool ("bool/" Equivalence<Bool>)]
+ [bit ("bit/" Equivalence<Bit>)]
[product]
[error]
[collection
@@ -35,7 +35,7 @@
(case> (#error.Success (#//.Structure (#//.Variant [leftsS right?S valueS])))
(let [tagS (if right?S (inc leftsS) leftsS)]
(and (n/= tagA tagS)
- (|> tagS (n/= (dec size)) (bool/= right?S))
+ (|> tagS (n/= (dec size)) (bit/= right?S))
(//primitive.corresponds? memberA valueS)))
_
diff --git a/stdlib/test/test/lux/language/syntax.lux b/stdlib/test/test/lux/language/syntax.lux
index 22420e3eb..8c93867aa 100644
--- a/stdlib/test/test/lux/language/syntax.lux
+++ b/stdlib/test/test/lux/language/syntax.lux
@@ -47,7 +47,7 @@
(r.Random Code)
(let [numeric^ (: (r.Random Code)
($_ r.either
- (|> r.bool (r/map code.bool))
+ (|> r.bit (r/map code.bit))
(|> r.nat (r/map code.nat))
(|> r.int (r/map code.int))
(|> r.rev (r/map code.rev))
@@ -116,7 +116,7 @@
(do @
[numerator (|> r.nat (:: @ map (|>> (n/% +100) .int int-to-frac)))
denominator (|> r.nat (:: @ map (|>> (n/% +100) (n/max +1) .int int-to-frac)))
- signed? r.bool
+ signed? r.bit
#let [expected (|> numerator (f// denominator) (f/* (if signed? -1.0 1.0)))]]
(test "Can parse frac ratio syntax."
(case (&.read "" (dict.new text.Hash<Text>)
diff --git a/stdlib/test/test/lux/language/type.lux b/stdlib/test/test/lux/language/type.lux
index 7be06000b..5f2cff09b 100644
--- a/stdlib/test/test/lux/language/type.lux
+++ b/stdlib/test/test/lux/language/type.lux
@@ -57,14 +57,14 @@
(test "Can apply quantified types (universal and existential quantification)."
(and (maybe.default false
(do maybe.Monad<Maybe>
- [partial (&.apply (list Bool) Ann)
+ [partial (&.apply (list Bit) Ann)
full (&.apply (list Int) partial)]
- (wrap (:: &.Equivalence<Type> = full (#.Product Bool Int)))))
- (|> (&.apply (list Bool) Text)
+ (wrap (:: &.Equivalence<Type> = full (#.Product Bit Int)))))
+ (|> (&.apply (list Bit) Text)
(case> #.None true _ false)))))
(context: "Naming"
- (let [base (#.Named ["" "a"] (#.Product Bool Int))
+ (let [base (#.Named ["" "a"] (#.Product Bit Int))
aliased (#.Named ["" "c"]
(#.Named ["" "b"]
base))]
diff --git a/stdlib/test/test/lux/language/type/check.lux b/stdlib/test/test/lux/language/type/check.lux
index 8fe7f2bf6..c2db4533c 100644
--- a/stdlib/test/test/lux/language/type/check.lux
+++ b/stdlib/test/test/lux/language/type/check.lux
@@ -50,7 +50,7 @@
)))))
(def: (valid-type? type)
- (-> Type Bool)
+ (-> Type Bit)
(case type
(#.Primitive name params)
(list.every? valid-type? params)
@@ -70,7 +70,7 @@
false))
(def: (type-checks? input)
- (-> (@.Check []) Bool)
+ (-> (@.Check []) Bit)
(case (@.run @.fresh-context input)
(#.Right [])
true
@@ -177,20 +177,20 @@
(test "Cannot rebind already bound type-vars."
(not (type-checks? (do @.Monad<Check>
[[id var] @.var
- _ (@.check var .Bool)]
+ _ (@.check var .Bit)]
(@.check var .Nat)))))
(test "If the type bound to a var is a super-type to another, then the var is also a super-type."
(type-checks? (do @.Monad<Check>
[[id var] @.var
_ (@.check var Any)]
- (@.check var .Bool))))
+ (@.check var .Bit))))
(test "If the type bound to a var is a sub-type of another, then the var is also a sub-type."
(type-checks? (do @.Monad<Check>
[[id var] @.var
_ (@.check var Nothing)]
- (@.check .Bool var))))
+ (@.check .Bit var))))
))
(def: (build-ring num-connections)
diff --git a/stdlib/test/test/lux/macro/code.lux b/stdlib/test/test/lux/macro/code.lux
index 6c5a28265..0dfcd8fa0 100644
--- a/stdlib/test/test/lux/macro/code.lux
+++ b/stdlib/test/test/lux/macro/code.lux
@@ -18,17 +18,17 @@
(and (text/= <text> (&.to-text <expr>))
(:: &.Equivalence<Code> = <expr> <expr>)))]
- [(&.bool true) "true"]
- [(&.bool false) "false"]
- [(&.int 123) "123"]
- [(&.frac 123.0) "123.0"]
- [(&.text "\n") "\"\\n\""]
- [(&.tag ["yolo" "lol"]) "#yolo.lol"]
- [(&.symbol ["yolo" "lol"]) "yolo.lol"]
- [(&.form (list (&.bool true) (&.int 123))) "(true 123)"]
- [(&.tuple (list (&.bool true) (&.int 123))) "[true 123]"]
- [(&.record (list [(&.bool true) (&.int 123)])) "{true 123}"]
- [(&.local-tag "lol") "#lol"]
- [(&.local-symbol "lol") "lol"]
+ [(&.bit true) "true"]
+ [(&.bit false) "false"]
+ [(&.int 123) "123"]
+ [(&.frac 123.0) "123.0"]
+ [(&.text "\n") "\"\\n\""]
+ [(&.tag ["yolo" "lol"]) "#yolo.lol"]
+ [(&.symbol ["yolo" "lol"]) "yolo.lol"]
+ [(&.form (list (&.bit true) (&.int 123))) "(true 123)"]
+ [(&.tuple (list (&.bit true) (&.int 123))) "[true 123]"]
+ [(&.record (list [(&.bit true) (&.int 123)])) "{true 123}"]
+ [(&.local-tag "lol") "#lol"]
+ [(&.local-symbol "lol") "lol"]
)]
($_ seq <tests>)))
diff --git a/stdlib/test/test/lux/macro/poly/equivalence.lux b/stdlib/test/test/lux/macro/poly/equivalence.lux
index 3ae57cd40..d6b48428a 100644
--- a/stdlib/test/test/lux/macro/poly/equivalence.lux
+++ b/stdlib/test/test/lux/macro/poly/equivalence.lux
@@ -5,7 +5,7 @@
[monad (#+ do Monad)]
[equivalence (#+ Equivalence)]]
[data
- [bool]
+ [bit]
[maybe]
[number ("int/" Number<Int>)]
["." text
@@ -20,7 +20,7 @@
## [Utils]
(type: Variant
- (#Case0 Bool)
+ (#Case0 Bit)
(#Case1 Int)
(#Case2 Frac))
@@ -29,7 +29,7 @@
(#Addition Frac Recursive))
(type: Record
- {#bool Bool
+ {#bit Bit
#int Int
#frac Frac
#text Text
@@ -51,13 +51,13 @@
[size (:: @ map (n/% +2) r.nat)
#let [gen-int (|> r.int (:: @ map (|>> int/abs (i/% 1_000_000))))]]
($_ r.seq
- r.bool
+ r.bit
gen-int
r.frac
(r.unicode size)
(r.maybe gen-int)
(r.list size gen-int)
- ($_ r.alt r.bool gen-int r.frac)
+ ($_ r.alt r.bit gen-int r.frac)
($_ r.seq gen-int r.frac (r.unicode size))
gen-recursive)))
diff --git a/stdlib/test/test/lux/macro/syntax.lux b/stdlib/test/test/lux/macro/syntax.lux
index 8d2b5ff8c..35e25734f 100644
--- a/stdlib/test/test/lux/macro/syntax.lux
+++ b/stdlib/test/test/lux/macro/syntax.lux
@@ -6,7 +6,7 @@
[equivalence (#+ Equivalence)]
["p" parser]]
[data
- [bool]
+ [bit]
[ident]
["e" error]
[number]
@@ -21,7 +21,7 @@
## [Utils]
(def: (enforced? parser input)
- (-> (Syntax []) (List Code) Bool)
+ (-> (Syntax []) (List Code) Bit)
(case (p.run input parser)
(#.Right [_ []])
true
@@ -30,7 +30,7 @@
false))
(def: (found? parser input)
- (-> (Syntax Bool) (List Code) Bool)
+ (-> (Syntax Bit) (List Code) Bit)
(case (p.run input parser)
(#.Right [_ true])
true
@@ -39,7 +39,7 @@
false))
(def: (equals? Equivalence<a> reference parser input)
- (All [a] (-> (Equivalence a) a (Syntax a) (List Code) Bool))
+ (All [a] (-> (Equivalence a) a (Syntax a) (List Code) Bit))
(case (p.run input parser)
(#.Right [_ output])
(:: Equivalence<a> = reference output)
@@ -48,7 +48,7 @@
false))
(def: (fails? input)
- (All [a] (-> (e.Error a) Bool))
+ (All [a] (-> (e.Error a) Bit))
(case input
(#.Left _)
true
@@ -73,7 +73,7 @@
(found? (s.this? (<ctor> <value>)) (list (<ctor> <value>)))
(enforced? (s.this (<ctor> <value>)) (list (<ctor> <value>)))))]
- ["Can parse Bool syntax." true code.bool bool.Equivalence<Bool> s.bool]
+ ["Can parse Bit syntax." true code.bit bit.Equivalence<Bit> s.bit]
["Can parse Nat syntax." +123 code.nat number.Equivalence<Nat> s.nat]
["Can parse Int syntax." 123 code.int number.Equivalence<Int> s.int]
["Can parse Rev syntax." .123 code.rev number.Equivalence<Rev> s.rev]
@@ -105,21 +105,21 @@
[<group-tests> (do-template [<type> <parser> <ctor>]
[(test (format "Can parse " <type> " syntax.")
(and (match [true 123]
- (p.run (list (<ctor> (list (code.bool true) (code.int 123))))
- (<parser> (p.seq s.bool s.int))))
+ (p.run (list (<ctor> (list (code.bit true) (code.int 123))))
+ (<parser> (p.seq s.bit s.int))))
(match true
- (p.run (list (<ctor> (list (code.bool true))))
- (<parser> s.bool)))
- (fails? (p.run (list (<ctor> (list (code.bool true) (code.int 123))))
- (<parser> s.bool)))
+ (p.run (list (<ctor> (list (code.bit true))))
+ (<parser> s.bit)))
+ (fails? (p.run (list (<ctor> (list (code.bit true) (code.int 123))))
+ (<parser> s.bit)))
(match (#.Left true)
- (p.run (list (<ctor> (list (code.bool true))))
- (<parser> (p.alt s.bool s.int))))
+ (p.run (list (<ctor> (list (code.bit true))))
+ (<parser> (p.alt s.bit s.int))))
(match (#.Right 123)
(p.run (list (<ctor> (list (code.int 123))))
- (<parser> (p.alt s.bool s.int))))
+ (<parser> (p.alt s.bit s.int))))
(fails? (p.run (list (<ctor> (list (code.frac 123.0))))
- (<parser> (p.alt s.bool s.int))))))]
+ (<parser> (p.alt s.bit s.int))))))]
["form" s.form code.form]
["tuple" s.tuple code.tuple])]
@@ -128,15 +128,15 @@
(test "Can parse record syntax."
(match [true 123]
- (p.run (list (code.record (list [(code.bool true) (code.int 123)])))
- (s.record (p.seq s.bool s.int)))))
+ (p.run (list (code.record (list [(code.bit true) (code.int 123)])))
+ (s.record (p.seq s.bit s.int)))))
)))
(context: "Combinators"
($_ seq
(test "Can parse any Code."
- (match [_ (#.Bool true)]
- (p.run (list (code.bool true) (code.int 123))
+ (match [_ (#.Bit true)]
+ (p.run (list (code.bit true) (code.int 123))
s.any)))
(test "Can check whether the end has been reached."
@@ -144,13 +144,13 @@
(p.run (list)
s.end?))
(match false
- (p.run (list (code.bool true))
+ (p.run (list (code.bit true))
s.end?))))
(test "Can ensure the end has been reached."
(and (match []
(p.run (list)
s.end!))
- (fails? (p.run (list (code.bool true))
+ (fails? (p.run (list (code.bit true))
s.end!))))
))
diff --git a/stdlib/test/test/lux/math.lux b/stdlib/test/test/lux/math.lux
index ab12c4894..920b0c951 100644
--- a/stdlib/test/test/lux/math.lux
+++ b/stdlib/test/test/lux/math.lux
@@ -4,21 +4,21 @@
[control
[monad (#+ do Monad)]]
[data
- [bool ("bool/" Equivalence<Bool>)]
+ [bit ("bit/" Equivalence<Bit>)]
[number ("frac/" Number<Frac>)]]
["&" math
["r" random]]]
lux/test)
(def: (within? margin-of-error standard value)
- (-> Frac Frac Frac Bool)
+ (-> Frac Frac Frac Bit)
(f/< margin-of-error
(frac/abs (f/- standard value))))
(def: margin Frac 0.0000001)
(def: (trigonometric-symmetry forward backward angle)
- (-> (-> Frac Frac) (-> Frac Frac) Frac Bool)
+ (-> (-> Frac Frac) (-> Frac Frac) Frac Bit)
(let [normal (|> angle forward backward)]
(|> normal forward backward (within? margin normal))))
@@ -114,12 +114,12 @@
(&.infix [(n/* +3 +9) &.n/gcd +450])))
(test "Can use non-numerical functions/macros as operators."
- (bool/= (and (n/< y x) (n/< z y))
- (&.infix [[x n/< y] and [y n/< z]])))
-
- (test "Can combine boolean operations in special ways via special keywords."
- (and (bool/= (and (n/< y x) (n/< z y))
- (&.infix [#and x n/< y n/< z]))
- (bool/= (and (n/< y x) (n/> z y))
- (&.infix [#and x n/< y n/> z]))))
+ (bit/= (and (n/< y x) (n/< z y))
+ (&.infix [[x n/< y] and [y n/< z]])))
+
+ (test "Can combine bit operations in special ways via special keywords."
+ (and (bit/= (and (n/< y x) (n/< z y))
+ (&.infix [#and x n/< y n/< z]))
+ (bit/= (and (n/< y x) (n/> z y))
+ (&.infix [#and x n/< y n/> z]))))
))))
diff --git a/stdlib/test/test/lux/math/logic/fuzzy.lux b/stdlib/test/test/lux/math/logic/fuzzy.lux
index 53e183b35..104c0cf76 100644
--- a/stdlib/test/test/lux/math/logic/fuzzy.lux
+++ b/stdlib/test/test/lux/math/logic/fuzzy.lux
@@ -4,7 +4,7 @@
[control
[monad (#+ do Monad)]]
[data
- [bool ("bool/" Equivalence<Bool>)]
+ [bit ("bit/" Equivalence<Bit>)]
[number]
[text
format]
@@ -46,14 +46,14 @@
(r/= ~false (&.membership top triangle))))
(test "Values within range, will have membership > 0."
- (bool/= (r/> ~false (&.membership sample triangle))
- (and (<gt> bottom sample)
- (<lt> top sample))))
+ (bit/= (r/> ~false (&.membership sample triangle))
+ (and (<gt> bottom sample)
+ (<lt> top sample))))
(test "Values outside of range, will have membership = 0."
- (bool/= (r/= ~false (&.membership sample triangle))
- (or (<lte> bottom sample)
- (<gte> top sample))))
+ (bit/= (r/= ~false (&.membership sample triangle))
+ (or (<lte> bottom sample)
+ (<gte> top sample))))
))))]
["Rev" number.Hash<Rev> r.rev &.triangle r/< r/<= r/> r/>=]
@@ -88,19 +88,19 @@
(r/= ~false (&.membership top trapezoid))))
(test "Values within inner range will have membership = 1"
- (bool/= (r/= ~true (&.membership sample trapezoid))
- (and (<gte> middle-bottom sample)
- (<lte> middle-top sample))))
+ (bit/= (r/= ~true (&.membership sample trapezoid))
+ (and (<gte> middle-bottom sample)
+ (<lte> middle-top sample))))
(test "Values within range, will have membership > 0."
- (bool/= (r/> ~false (&.membership sample trapezoid))
- (and (<gt> bottom sample)
- (<lt> top sample))))
+ (bit/= (r/> ~false (&.membership sample trapezoid))
+ (and (<gt> bottom sample)
+ (<lt> top sample))))
(test "Values outside of range, will have membership = 0."
- (bool/= (r/= ~false (&.membership sample trapezoid))
- (or (<lte> bottom sample)
- (<gte> top sample))))
+ (bit/= (r/= ~false (&.membership sample trapezoid))
+ (or (<lte> bottom sample)
+ (<gte> top sample))))
))))]
["Rev" number.Hash<Rev> r.rev &.trapezoid r/< r/<= r/> r/>=]
@@ -142,10 +142,10 @@
(~not (&.membership sample (&.complement left)))))
(test "Membership in the difference will never be higher than in the set being subtracted."
- (bool/= (r/> (&.membership sample right)
- (&.membership sample left))
- (r/< (&.membership sample left)
- (&.membership sample (&.difference left right)))))
+ (bit/= (r/> (&.membership sample right)
+ (&.membership sample left))
+ (r/< (&.membership sample left)
+ (&.membership sample (&.difference left right)))))
))))
(context: "From predicates and sets"
@@ -156,13 +156,13 @@
($_ seq
(test "Values that satisfy a predicate have membership = 1.
Values that don't have membership = 0."
- (bool/= (r/= ~true (&.membership sample (&.from-predicate n/even?)))
- (n/even? sample)))
+ (bit/= (r/= ~true (&.membership sample (&.from-predicate n/even?)))
+ (n/even? sample)))
(test "Values that belong to a set have membership = 1.
Values that don't have membership = 0."
- (bool/= (r/= ~true (&.membership sample (&.from-set set-10)))
- (set.member? set-10 sample)))
+ (bit/= (r/= ~true (&.membership sample (&.from-set set-10)))
+ (set.member? set-10 sample)))
))))
(context: "Thresholds"
@@ -175,10 +175,10 @@
member? (&.to-predicate threshold fuzzy)]]
($_ seq
(test "Can increase the threshold of membership of a fuzzy set."
- (bool/= (r/> ~false (&.membership sample vip-fuzzy))
- (r/> threshold (&.membership sample fuzzy))))
+ (bit/= (r/> ~false (&.membership sample vip-fuzzy))
+ (r/> threshold (&.membership sample fuzzy))))
(test "Can turn fuzzy sets into predicates through a threshold."
- (bool/= (member? sample)
- (r/> threshold (&.membership sample fuzzy))))
+ (bit/= (member? sample)
+ (r/> threshold (&.membership sample fuzzy))))
))))
diff --git a/stdlib/test/test/lux/math/modular.lux b/stdlib/test/test/lux/math/modular.lux
index 8bbaf1292..47b8b8aba 100644
--- a/stdlib/test/test/lux/math/modular.lux
+++ b/stdlib/test/test/lux/math/modular.lux
@@ -4,7 +4,7 @@
[monad (#+ do)]]
[data
[product]
- [bool ("bool/" Equivalence<Bool>)]
+ [bit ("bit/" Equivalence<Bit>)]
["e" error]
[text
format]]
@@ -39,20 +39,20 @@
(def: (comparison m/? i/?)
(All [m]
- (-> (-> (/.Mod m) (/.Mod m) Bool)
- (-> Int Int Bool)
- (-> (/.Mod m) (/.Mod m) Bool)))
+ (-> (-> (/.Mod m) (/.Mod m) Bit)
+ (-> Int Int Bit)
+ (-> (/.Mod m) (/.Mod m) Bit)))
(function (_ param subject)
- (bool/= (m/? param subject)
- (i/? (value param)
- (value subject)))))
+ (bit/= (m/? param subject)
+ (i/? (value param)
+ (value subject)))))
(def: (arithmetic modulus m/! i/!)
(All [m]
(-> (/.Modulus m)
(-> (/.Mod m) (/.Mod m) (/.Mod m))
(-> Int Int Int)
- (-> (/.Mod m) (/.Mod m) Bool)))
+ (-> (/.Mod m) (/.Mod m) Bit)))
(function (_ param subject)
(|> (i/! (value param)
(value subject))
@@ -91,13 +91,13 @@
((comparison /.m/>= i/>=) param subject)))
(test "Mod'ed values are ordered."
- (and (bool/= (/.m/< param subject)
- (not (/.m/>= param subject)))
- (bool/= (/.m/> param subject)
- (not (/.m/<= param subject)))
- (bool/= (/.m/= param subject)
- (not (or (/.m/< param subject)
- (/.m/> param subject))))))
+ (and (bit/= (/.m/< param subject)
+ (not (/.m/>= param subject)))
+ (bit/= (/.m/> param subject)
+ (not (/.m/<= param subject)))
+ (bit/= (/.m/= param subject)
+ (not (or (/.m/< param subject)
+ (/.m/> param subject))))))
(test "Can do arithmetic."
(and ((arithmetic normalM /.m/+ i/+) param subject)
@@ -145,6 +145,6 @@
(/.congruent? normalM _subject _subject))
(test "If 2 numbers are congruent under a modulus, then they must also be equal under the same modulus."
- (bool/= (/.congruent? normalM _param _subject)
- (/.m/= param subject)))
+ (bit/= (/.congruent? normalM _param _subject)
+ (/.m/= param subject)))
))))
diff --git a/stdlib/test/test/lux/type/implicit.lux b/stdlib/test/test/lux/type/implicit.lux
index e19f672e0..71e2f29c6 100644
--- a/stdlib/test/test/lux/type/implicit.lux
+++ b/stdlib/test/test/lux/type/implicit.lux
@@ -6,7 +6,7 @@
[functor]
[monad (#+ do Monad)]]
[data
- [bool ("bool/" Equivalence<Bool>)]
+ [bit ("bit/" Equivalence<Bit>)]
[number]
[collection [list]]]
[math
@@ -22,8 +22,8 @@
($_ seq
(test "Can automatically select first-order structures."
(let [(^open "list/") (list.Equivalence<List> number.Equivalence<Nat>)]
- (and (bool/= (:: number.Equivalence<Nat> = x y)
- (::: = x y))
+ (and (bit/= (:: number.Equivalence<Nat> = x y)
+ (::: = x y))
(list/= (list.n/range +1 +10)
(::: map inc (list.n/range +0 +9)))
)))
diff --git a/stdlib/test/test/lux/type/object/protocol.lux b/stdlib/test/test/lux/type/object/protocol.lux
index 0ec93442b..2e2ae212f 100644
--- a/stdlib/test/test/lux/type/object/protocol.lux
+++ b/stdlib/test/test/lux/type/object/protocol.lux
@@ -23,9 +23,9 @@
((counter +0) (message [])))
(protocol: Protocol0
- (method0 [Bool Nat Text] Bool)
- (method1 [Nat Text Bool] Nat)
- (method2 [Text Bool Nat] Text))
+ (method0 [Bit Nat Text] Bit)
+ (method1 [Nat Text Bit] Nat)
+ (method2 [Text Bit Nat] Text))
(type: Object0 (Object Protocol0))
diff --git a/stdlib/test/test/lux/world/blob.lux b/stdlib/test/test/lux/world/blob.lux
index f93b4e5dd..ea9dc4087 100644
--- a/stdlib/test/test/lux/world/blob.lux
+++ b/stdlib/test/test/lux/world/blob.lux
@@ -20,7 +20,7 @@
["_eq" equivalence]]]])
(def: (succeed result)
- (-> (e.Error Bool) Bool)
+ (-> (e.Error Bit) Bit)
(case result
(#e.Error _)
false
@@ -40,7 +40,7 @@
(:: r.Monad<Random> wrap output)))))
(def: (bits-io bytes read write value)
- (-> Nat (-> Nat /.Blob (e.Error Nat)) (-> Nat Nat /.Blob (e.Error Any)) Nat Bool)
+ (-> Nat (-> Nat /.Blob (e.Error Nat)) (-> Nat Nat /.Blob (e.Error Any)) Nat Bit)
(let [blob (/.create +8)
bits (n/* +8 bytes)
capped-value (|> +1 (i64.left-shift bits) dec (i64.and value))]
diff --git a/stdlib/test/test/lux/world/net/tcp.lux b/stdlib/test/test/lux/world/net/tcp.lux
index 26b7703ea..1c315c7f5 100644
--- a/stdlib/test/test/lux/world/net/tcp.lux
+++ b/stdlib/test/test/lux/world/net/tcp.lux
@@ -42,7 +42,7 @@
(wrap (do P.Monad<Promise>
[result (do T.Monad<Task>
[[server-close server] (@.server port)
- #let [from-worked? (: (T.Task Bool)
+ #let [from-worked? (: (T.Task Bit)
(P.promise #.Nil))
_ (frp/map (function (_ socket)
(do @