diff options
Diffstat (limited to 'stdlib/test')
-rw-r--r-- | stdlib/test/test/lux.lux | 10 | ||||
-rw-r--r-- | stdlib/test/test/lux/data/color.lux | 54 | ||||
-rw-r--r-- | stdlib/test/test/lux/data/format/json.lux | 46 | ||||
-rw-r--r-- | stdlib/test/test/lux/data/number.lux | 34 | ||||
-rw-r--r-- | stdlib/test/test/lux/data/number/complex.lux | 58 | ||||
-rw-r--r-- | stdlib/test/test/lux/data/number/ratio.lux | 1 | ||||
-rw-r--r-- | stdlib/test/test/lux/host.js.lux | 4 | ||||
-rw-r--r-- | stdlib/test/test/lux/macro/code.lux | 2 | ||||
-rw-r--r-- | stdlib/test/test/lux/macro/poly/eq.lux | 20 | ||||
-rw-r--r-- | stdlib/test/test/lux/macro/syntax.lux | 4 | ||||
-rw-r--r-- | stdlib/test/test/lux/math.lux | 40 | ||||
-rw-r--r-- | stdlib/test/test/lux/math/logic/fuzzy.lux | 22 |
12 files changed, 147 insertions, 148 deletions
diff --git a/stdlib/test/test/lux.lux b/stdlib/test/test/lux.lux index dcf1997f0..41b3bc555 100644 --- a/stdlib/test/test/lux.lux +++ b/stdlib/test/test/lux.lux @@ -69,7 +69,7 @@ ["Int" R;int i.= i.< i.> i.<= i.>= i.min i.max] ["Nat" R;nat n.= n.< n.> n.<= n.>= n.min n.max] - ["Real" R;real r.= r.< r.> r.<= r.>= r.min r.max] + ["Frac" R;frac f.= f.< f.> f.<= f.>= f.min f.max] ["Deg" R;deg d.= d.< d.> d.<= d.>= d.min d.max] ) @@ -117,7 +117,7 @@ ["Nat" R;nat n.= n.+ n.- n.* n./ n.% n.> +0 +1 +1000000 %n (n.% +1000) id] ["Int" R;int i.= i.+ i.- i.* i./ i.% i.> 0 1 1000000 %i (i.% 1000) id] - ["Real" R;real r.= r.+ r.- r.* r./ r.% r.> 0.0 1.0 1000000.0 %r id math;floor] + ["Frac" R;frac f.= f.+ f.- f.* f./ f.% f.> 0.0 1.0 1000000.0 %r id math;floor] ["Deg" R;deg d.= d.+ d.- d.* d./ d.% d.> .0 (_lux_proc ["deg" "max-value"] []) (_lux_proc ["deg" "max-value"] []) %f id id] ) @@ -130,9 +130,9 @@ ["Int->Nat" R;int int-to-nat nat-to-int i.= (i.% 1000000) %i %n] ["Nat->Int" R;nat nat-to-int int-to-nat n.= (n.% +1000000) %n %i] - ["Int->Real" R;int int-to-real real-to-int i.= (i.% 1000000) %i %r] - ["Real->Int" R;real real-to-int int-to-real r.= math;floor %r %i] - ## [R;real real-to-deg deg-to-real r.= (r.% 1.0) %r %f] + ["Int->Frac" R;int int-to-frac frac-to-int i.= (i.% 1000000) %i %r] + ["Frac->Int" R;frac frac-to-int int-to-frac f.= math;floor %r %i] + ## [R;frac frac-to-deg deg-to-frac f.= (f.% 1.0) %r %f] ) (context: "Simple macros and constructs" diff --git a/stdlib/test/test/lux/data/color.lux b/stdlib/test/test/lux/data/color.lux index 0187f9430..5ca3c95c3 100644 --- a/stdlib/test/test/lux/data/color.lux +++ b/stdlib/test/test/lux/data/color.lux @@ -3,7 +3,7 @@ (lux [io] (control [monad #+ do]) (data ["@" color] - [number "real/" Number<Real>]) + [number "frac/" Number<Frac>]) [math] ["r" math/random]) lux/test) @@ -14,28 +14,28 @@ (:: r;Monad<Random> map @;color))) (def: scale - (-> Nat Real) - (|>. nat-to-int int-to-real)) + (-> Nat Frac) + (|>. nat-to-int int-to-frac)) -(def: square (-> Real Real) (math;pow 2.0)) +(def: square (-> Frac Frac) (math;pow 2.0)) (def: (distance from to) - (-> @;Color @;Color Real) + (-> @;Color @;Color Frac) (let [[fr fg fb] (@;unpack from) [tr tg tb] (@;unpack to)] - (math;root2 ($_ r.+ - (|> (scale tr) (r.- (scale fr)) square) - (|> (scale tg) (r.- (scale fg)) square) - (|> (scale tb) (r.- (scale fb)) square))))) + (math;root2 ($_ f.+ + (|> (scale tr) (f.- (scale fr)) square) + (|> (scale tg) (f.- (scale fg)) square) + (|> (scale tb) (f.- (scale fb)) square))))) -(def: error-margin Real 1.8) +(def: error-margin Frac 1.8) (def: black @;Color (@;color [+0 +0 +0])) (def: white @;Color (@;color [+255 +255 +255])) (do-template [<field>] [(def: (<field> color) - (-> @;Color Real) + (-> @;Color Frac) (let [[hue saturation luminance] (@;to-hsl color)] <field>))] @@ -46,33 +46,33 @@ (context: "Color." [any color colorful (|> color - (r;filter (function [color] (|> (distance color black) (r.>= 100.0)))) - (r;filter (function [color] (|> (distance color white) (r.>= 100.0))))) + (r;filter (function [color] (|> (distance color black) (f.>= 100.0)))) + (r;filter (function [color] (|> (distance color white) (f.>= 100.0))))) mediocre (|> color (r;filter (|>. saturation ((function [saturation] - (and (r.>= 0.25 saturation) - (r.<= 0.75 saturation))))))) - ratio (|> r;real (r;filter (r.>= 0.5)))] + (and (f.>= 0.25 saturation) + (f.<= 0.75 saturation))))))) + ratio (|> r;frac (r;filter (f.>= 0.5)))] ($_ seq (test "Has equality." (:: @;Eq<Color> = any any)) (test "Can convert to/from HSL." (|> any @;to-hsl @;from-hsl (distance any) - (r.<= error-margin))) + (f.<= error-margin))) (test "Can convert to/from HSB." (|> any @;to-hsb @;from-hsb (distance any) - (r.<= error-margin))) + (f.<= error-margin))) (test "Can convert to/from CMYK." (|> any @;to-cmyk @;from-cmyk (distance any) - (r.<= error-margin))) + (f.<= error-margin))) (test "Can interpolate between 2 colors." - (and (r.<= (distance colorful black) + (and (f.<= (distance colorful black) (distance (@;darker ratio colorful) black)) - (r.<= (distance colorful white) + (f.<= (distance colorful white) (distance (@;brighter ratio colorful) white)))) (test "Can calculate complement." (let [~any (@;complement any) @@ -80,17 +80,17 @@ (and (not (@/= any ~any)) (@/= any (@;complement ~any))))) (test "Can saturate color." - (r.> (saturation mediocre) + (f.> (saturation mediocre) (saturation (@;saturate ratio mediocre)))) (test "Can de-saturate color." - (r.< (saturation mediocre) + (f.< (saturation mediocre) (saturation (@;de-saturate ratio mediocre)))) (test "Can gray-scale color." (let [gray'ed (@;gray-scale mediocre)] - (and (r.= 0.0 + (and (f.= 0.0 (saturation gray'ed)) (|> (luminance gray'ed) - (r.- (luminance mediocre)) - real/abs - (r.<= error-margin))))) + (f.- (luminance mediocre)) + frac/abs + (f.<= error-margin))))) )) diff --git a/stdlib/test/test/lux/data/format/json.lux b/stdlib/test/test/lux/data/format/json.lux index 68e1427ee..2dce7ad84 100644 --- a/stdlib/test/test/lux/data/format/json.lux +++ b/stdlib/test/test/lux/data/format/json.lux @@ -35,7 +35,7 @@ ($_ r;alt (:: @ wrap []) r;bool - (|> r;real (:: @ map (r.* 1_000_000.0))) + (|> r;frac (:: @ map (f.* 1_000_000.0))) (r;text size) (r;vector size gen-json) (r;dict text;Hash<Text> size (r;text size) gen-json) @@ -61,29 +61,29 @@ (type: Variant (#Case0 Bool) (#Case1 Text) - (#Case2 Real)) + (#Case2 Frac)) (type: #rec Recursive - (#Number Real) - (#Addition Real Recursive)) + (#Number Frac) + (#Addition Frac Recursive)) (type: Record {#unit Unit #bool Bool - #real Real + #frac Frac #text Text - #maybe (Maybe Real) - #list (List Real) + #maybe (Maybe Frac) + #list (List Frac) #variant Variant - #tuple [Bool Real Text] - #dict (d;Dict Text Real) + #tuple [Bool Frac Text] + #dict (d;Dict Text Frac) #recursive Recursive}) (def: gen-recursive (r;Random Recursive) (r;rec (function [gen-recursive] - (r;alt r;real - (r;seq r;real gen-recursive))))) + (r;alt r;frac + (r;seq r;frac gen-recursive))))) (derived: (poly/eq;Eq<?> Recursive)) @@ -94,13 +94,13 @@ ($_ r;seq (:: @ wrap []) r;bool - r;real + r;frac (r;text size) - (r;maybe r;real) - (r;list size r;real) - ($_ r;alt r;bool (r;text size) r;real) - ($_ r;seq r;bool r;real (r;text size)) - (r;dict text;Hash<Text> size (r;text size) r;real) + (r;maybe r;frac) + (r;list size r;frac) + ($_ r;alt r;bool (r;text size) r;frac) + ($_ r;seq r;bool r;frac (r;text size)) + (r;dict text;Hash<Text> size (r;text size) r;frac) gen-recursive ))) @@ -117,22 +117,22 @@ (:: text;Eq<Text> = left' right') [(#Case2 left') (#Case2 right')] - (r.= left' right') + (f.= left' right') _ false))] (and (:: bool;Eq<Bool> = (get@ #bool recL) (get@ #bool recR)) - (r.= (get@ #real recL) (get@ #real recR)) + (f.= (get@ #frac recL) (get@ #frac recR)) (:: text;Eq<Text> = (get@ #text recL) (get@ #text recR)) - (:: (maybe;Eq<Maybe> number;Eq<Real>) = (get@ #maybe recL) (get@ #maybe recR)) - (:: (list;Eq<List> number;Eq<Real>) = (get@ #list recL) (get@ #list recR)) + (:: (maybe;Eq<Maybe> number;Eq<Frac>) = (get@ #maybe recL) (get@ #maybe recR)) + (:: (list;Eq<List> number;Eq<Frac>) = (get@ #list recL) (get@ #list recR)) (variant/= (get@ #variant recL) (get@ #variant recR)) (let [[tL0 tL1 tL2] (get@ #tuple recL) [tR0 tR1 tR2] (get@ #tuple recR)] (and (:: bool;Eq<Bool> = tL0 tR0) - (r.= tL1 tR1) + (f.= tL1 tR1) (:: text;Eq<Text> = tL2 tR2))) - (:: (d;Eq<Dict> number;Eq<Real>) = (get@ #dict recL) (get@ #dict recR)) + (:: (d;Eq<Dict> number;Eq<Frac>) = (get@ #dict recL) (get@ #dict recR)) (:: Eq<Recursive> = (get@ #recursive recL) (get@ #recursive recR)) )))) diff --git a/stdlib/test/test/lux/data/number.lux b/stdlib/test/test/lux/data/number.lux index dc6a1ad29..b715119c6 100644 --- a/stdlib/test/test/lux/data/number.lux +++ b/stdlib/test/test/lux/data/number.lux @@ -20,7 +20,7 @@ ["Nat" R;nat Eq<Nat> Order<Nat>] ["Int" R;int Eq<Int> Order<Int>] - ["Real" R;real Eq<Real> Order<Real>] + ["Frac" R;frac Eq<Frac> Order<Frac>] ["Deg" R;deg Eq<Deg> Order<Deg>] ) @@ -31,7 +31,7 @@ (^open) <Order>]] (test "" (and (>= x (abs x)) ## abs(0.0) == 0.0 && negate(abs(0.0)) == -0.0 - (or (Text/= "Real" category) + (or (Text/= "Frac" category) (not (= x (negate x)))) (= x (negate (negate x))) ## There is loss of precision when multiplying @@ -41,7 +41,7 @@ ## ["Nat" R;nat Number<Nat>] ["Int" R;int Number<Int> Order<Int>] - ["Real" R;real Number<Real> Order<Real>] + ["Frac" R;frac Number<Frac> Order<Frac>] ["Deg" R;deg Number<Deg> Order<Deg>] ) @@ -76,7 +76,7 @@ ["Nat" R;nat Number<Nat> Order<Nat> Interval<Nat> (function [_] true)] ["Int" R;int Number<Int> Order<Int> Interval<Int> (function [_] true)] ## Both min and max values will be positive (thus, greater than zero) - ["Real" R;real Number<Real> Order<Real> Interval<Real> (r.> 0.0)] + ["Frac" R;frac Number<Frac> Order<Frac> Interval<Frac> (f.> 0.0)] ["Deg" R;deg Number<Deg> Order<Deg> Interval<Deg> (function [_] true)] ) @@ -99,10 +99,10 @@ ["Int/Mul" R;int Number<Int> Order<Int> Mul@Monoid<Int> (i.% 1000) (function [_] true)] ["Int/Min" R;int Number<Int> Order<Int> Min@Monoid<Int> (i.% 1000) (function [_] true)] ["Int/Max" R;int Number<Int> Order<Int> Max@Monoid<Int> (i.% 1000) (function [_] true)] - ["Real/Add" R;real Number<Real> Order<Real> Add@Monoid<Real> (r.% 1000.0) (r.> 0.0)] - ["Real/Mul" R;real Number<Real> Order<Real> Mul@Monoid<Real> (r.% 1000.0) (r.> 0.0)] - ["Real/Min" R;real Number<Real> Order<Real> Min@Monoid<Real> (r.% 1000.0) (r.> 0.0)] - ["Real/Max" R;real Number<Real> Order<Real> Max@Monoid<Real> (r.% 1000.0) (r.> 0.0)] + ["Frac/Add" R;frac Number<Frac> Order<Frac> Add@Monoid<Frac> (f.% 1000.0) (f.> 0.0)] + ["Frac/Mul" R;frac Number<Frac> Order<Frac> Mul@Monoid<Frac> (f.% 1000.0) (f.> 0.0)] + ["Frac/Min" R;frac Number<Frac> Order<Frac> Min@Monoid<Frac> (f.% 1000.0) (f.> 0.0)] + ["Frac/Max" R;frac Number<Frac> Order<Frac> Max@Monoid<Frac> (f.% 1000.0) (f.> 0.0)] ["Deg/Add" R;deg Number<Deg> Order<Deg> Add@Monoid<Deg> (d.% .125) (function [_] true)] ## ["Deg/Mul" R;deg Number<Deg> Order<Deg> Mul@Monoid<Deg> (d.% .125) (function [_] true)] ["Deg/Min" R;deg Number<Deg> Order<Deg> Min@Monoid<Deg> (d.% .125) (function [_] true)] @@ -137,15 +137,15 @@ ["Deg/Decimal" R;deg Eq<Deg> Codec<Text,Deg>] ["Deg/Hex" R;deg Eq<Deg> Hex@Codec<Text,Deg>] - ["Real/Binary" R;real Eq<Real> Binary@Codec<Text,Real>] - ["Real/Octal" R;real Eq<Real> Octal@Codec<Text,Real>] - ["Real/Decimal" R;real Eq<Real> Codec<Text,Real>] - ["Real/Hex" R;real Eq<Real> Hex@Codec<Text,Real>] + ["Frac/Binary" R;frac Eq<Frac> Binary@Codec<Text,Frac>] + ["Frac/Octal" R;frac Eq<Frac> Octal@Codec<Text,Frac>] + ["Frac/Decimal" R;frac Eq<Frac> Codec<Text,Frac>] + ["Frac/Hex" R;frac Eq<Frac> Hex@Codec<Text,Frac>] ) -(context: "Can convert real values to/from their bit patterns." - [raw R;real +(context: "Can convert frac values to/from their bit patterns." + [raw R;frac factor (|> R;nat (:: @ map (|>. (n.% +1000) (n.max +1)))) - #let [sample (|> factor nat-to-int int-to-real (r.* raw))]] - (test "Can convert real values to/from their bit patterns." - (|> sample real-to-bits bits-to-real (r.= sample)))) + #let [sample (|> factor nat-to-int int-to-frac (f.* raw))]] + (test "Can convert frac values to/from their bit patterns." + (|> sample frac-to-bits bits-to-frac (f.= sample)))) diff --git a/stdlib/test/test/lux/data/number/complex.lux b/stdlib/test/test/lux/data/number/complex.lux index 52ad12afb..78155e061 100644 --- a/stdlib/test/test/lux/data/number/complex.lux +++ b/stdlib/test/test/lux/data/number/complex.lux @@ -6,7 +6,7 @@ (data [text "Text/" Monoid<Text>] text/format [bool "b/" Eq<Bool>] - [number "r/" Number<Real>] + [number "f/" Number<Frac>] ["&" number/complex] (coll [list "List/" Fold<List> Functor<List>]) [product]) @@ -17,23 +17,23 @@ ## Based on org.apache.commons.math4.complex.Complex ## https://github.com/apache/commons-math/blob/master/src/test/java/org/apache/commons/math4/complex/ComplexTest.java -(def: margin-of-error Real 1.0e-10) +(def: margin-of-error Frac 1.0e-10) (def: (within? margin standard value) - (-> Real &;Complex &;Complex Bool) - (let [real-dist (r/abs (r.- (get@ #&;real standard) + (-> Frac &;Complex &;Complex Bool) + (let [real-dist (f/abs (f.- (get@ #&;real standard) (get@ #&;real value))) - imgn-dist (r/abs (r.- (get@ #&;imaginary standard) + imgn-dist (f/abs (f.- (get@ #&;imaginary standard) (get@ #&;imaginary value)))] - (and (r.< margin real-dist) - (r.< margin imgn-dist)))) + (and (f.< margin real-dist) + (f.< margin imgn-dist)))) (def: gen-dim - (R;Random Real) + (R;Random Frac) (do R;Monad<Random> [factor (|> R;nat (:: @ map (|>. (n.% +1000) (n.max +1)))) - measure (|> R;real (R;filter (r.> 0.0)))] - (wrap (r.* (|> factor nat-to-int int-to-real) + measure (|> R;frac (R;filter (f.> 0.0)))] + (wrap (f.* (|> factor nat-to-int int-to-frac) measure)))) (def: gen-complex @@ -49,8 +49,8 @@ ($_ seq (test "Can build and tear apart complex numbers" (let [r+i (&;complex real imaginary)] - (and (r.= real (get@ #&;real r+i)) - (r.= imaginary (get@ #&;imaginary r+i))))) + (and (f.= real (get@ #&;real r+i)) + (f.= imaginary (get@ #&;imaginary r+i))))) (test "If either the real part or the imaginary part is NaN, the composite is NaN." (and (&;not-a-number? (&;complex number;not-a-number imaginary)) @@ -64,18 +64,18 @@ (test "Absolute value of complex >= absolute value of any of the parts." (let [r+i (&;complex real imaginary) abs (get@ #&;real (&;c.abs r+i))] - (and (r.>= (r/abs real) abs) - (r.>= (r/abs imaginary) abs)))) + (and (f.>= (f/abs real) abs) + (f.>= (f/abs imaginary) abs)))) (test "The absolute value of a complex number involving a NaN on either dimension, results in a NaN value." (and (number;not-a-number? (get@ #&;real (&;c.abs (&;complex number;not-a-number imaginary)))) (number;not-a-number? (get@ #&;real (&;c.abs (&;complex real number;not-a-number)))))) (test "The absolute value of a complex number involving an infinity on either dimension, results in an infinite value." - (and (r.= number;positive-infinity (get@ #&;real (&;c.abs (&;complex number;positive-infinity imaginary)))) - (r.= number;positive-infinity (get@ #&;real (&;c.abs (&;complex real number;positive-infinity)))) - (r.= number;positive-infinity (get@ #&;real (&;c.abs (&;complex number;negative-infinity imaginary)))) - (r.= number;positive-infinity (get@ #&;real (&;c.abs (&;complex real number;negative-infinity)))))) + (and (f.= number;positive-infinity (get@ #&;real (&;c.abs (&;complex number;positive-infinity imaginary)))) + (f.= number;positive-infinity (get@ #&;real (&;c.abs (&;complex real number;positive-infinity)))) + (f.= number;positive-infinity (get@ #&;real (&;c.abs (&;complex number;negative-infinity imaginary)))) + (f.= number;positive-infinity (get@ #&;real (&;c.abs (&;complex real number;negative-infinity)))))) )) (context: "Addidion, substraction, multiplication and division" @@ -86,17 +86,17 @@ (test "Adding 2 complex numbers is the same as adding their parts." (let [z (&;c.+ y x)] (and (&;c.= z - (&;complex (r.+ (get@ #&;real y) + (&;complex (f.+ (get@ #&;real y) (get@ #&;real x)) - (r.+ (get@ #&;imaginary y) + (f.+ (get@ #&;imaginary y) (get@ #&;imaginary x))))))) (test "Subtracting 2 complex numbers is the same as adding their parts." (let [z (&;c.- y x)] (and (&;c.= z - (&;complex (r.- (get@ #&;real y) + (&;complex (f.- (get@ #&;real y) (get@ #&;real x)) - (r.- (get@ #&;imaginary y) + (f.- (get@ #&;imaginary y) (get@ #&;imaginary x))))))) (test "Subtraction is the inverse of addition." @@ -126,9 +126,9 @@ ($_ seq (test "Conjugate has same real part as original, and opposite of imaginary part." (let [cx (&;conjugate x)] - (and (r.= (get@ #&;real x) + (and (f.= (get@ #&;real x) (get@ #&;real cx)) - (r.= (r/negate (get@ #&;imaginary x)) + (f.= (f/negate (get@ #&;imaginary x)) (get@ #&;imaginary cx))))) (test "The reciprocal functions is its own inverse." @@ -139,9 +139,9 @@ (test "Absolute value of signum is always root2(2), 1 or 0." (let [signum-abs (|> x &;c.signum &;c.abs (get@ #&;real))] - (or (r.= 0.0 signum-abs) - (r.= 1.0 signum-abs) - (r.= (math;root2 2.0) signum-abs)))) + (or (f.= 0.0 signum-abs) + (f.= 1.0 signum-abs) + (f.= (math;root2 2.0) signum-abs)))) (test "Negation is its own inverse." (let [there (&;c.negate x) @@ -150,7 +150,7 @@ (&;c.= back-again x)))) (test "Negation doesn't change the absolute value." - (r.= (get@ #&;real (&;c.abs x)) + (f.= (get@ #&;real (&;c.abs x)) (get@ #&;real (&;c.abs (&;c.negate x))))) )) @@ -184,7 +184,7 @@ (test "Can calculate the N roots for any complex number." (|> sample (&;nth-roots degree) - (List/map (&;pow' (|> degree nat-to-int int-to-real))) + (List/map (&;pow' (|> degree nat-to-int int-to-frac))) (list;every? (within? margin-of-error sample))))) (context: "Codec" diff --git a/stdlib/test/test/lux/data/number/ratio.lux b/stdlib/test/test/lux/data/number/ratio.lux index 968f38b96..a2eb4f53d 100644 --- a/stdlib/test/test/lux/data/number/ratio.lux +++ b/stdlib/test/test/lux/data/number/ratio.lux @@ -6,7 +6,6 @@ (data [text "Text/" Monoid<Text>] text/format [bool "b/" Eq<Bool>] - [number "r/" Number<Real>] ["&" number/ratio "&/" Number<Ratio>] (coll [list "List/" Fold<List> Functor<List>]) [product]) diff --git a/stdlib/test/test/lux/host.js.lux b/stdlib/test/test/lux/host.js.lux index 92ac8ddb4..93e90bbfe 100644 --- a/stdlib/test/test/lux/host.js.lux +++ b/stdlib/test/test/lux/host.js.lux @@ -25,7 +25,7 @@ (test "Can call JavaScript functions" (and (is 124.0 - (&;call! (&;ref "Math.ceil" &;Function) [123.45] Real)) + (&;call! (&;ref "Math.ceil" &;Function) [123.45] Frac)) (is 124.0 - (&;call! (&;ref "Math") "ceil" [123.45] Real)))) + (&;call! (&;ref "Math") "ceil" [123.45] Frac)))) )) diff --git a/stdlib/test/test/lux/macro/code.lux b/stdlib/test/test/lux/macro/code.lux index c01a370a2..ff21fd0c9 100644 --- a/stdlib/test/test/lux/macro/code.lux +++ b/stdlib/test/test/lux/macro/code.lux @@ -19,7 +19,7 @@ [(&;bool true) "true"] [(&;bool false) "false"] [(&;int 123) "123"] - [(&;real 123.0) "123.0"] + [(&;frac 123.0) "123.0"] [(&;text "\n") "\"\\n\""] [(&;tag ["yolo" "lol"]) "#yolo;lol"] [(&;symbol ["yolo" "lol"]) "yolo;lol"] diff --git a/stdlib/test/test/lux/macro/poly/eq.lux b/stdlib/test/test/lux/macro/poly/eq.lux index 367ac1674..525b668a8 100644 --- a/stdlib/test/test/lux/macro/poly/eq.lux +++ b/stdlib/test/test/lux/macro/poly/eq.lux @@ -19,29 +19,29 @@ (type: Variant (#Case0 Bool) (#Case1 Int) - (#Case2 Real)) + (#Case2 Frac)) (type: #rec Recursive - (#Number Real) - (#Addition Real Recursive)) + (#Number Frac) + (#Addition Frac Recursive)) (type: Record {#unit Unit #bool Bool #int Int - #real Real + #frac Frac #text Text #maybe (Maybe Int) #list (List Int) #variant Variant - #tuple [Int Real Text] + #tuple [Int Frac Text] #recursive Recursive}) (def: gen-recursive (r;Random Recursive) (r;rec (function [gen-recursive] - (r;alt r;real - (r;seq r;real gen-recursive))))) + (r;alt r;frac + (r;seq r;frac gen-recursive))))) (def: gen-record (r;Random Record) @@ -52,12 +52,12 @@ (:: @ wrap []) r;bool gen-int - r;real + r;frac (r;text size) (r;maybe gen-int) (r;list size gen-int) - ($_ r;alt r;bool gen-int r;real) - ($_ r;seq gen-int r;real (r;text size)) + ($_ r;alt r;bool gen-int r;frac) + ($_ r;seq gen-int r;frac (r;text size)) gen-recursive))) (derived: (&;Eq<?> Record)) diff --git a/stdlib/test/test/lux/macro/syntax.lux b/stdlib/test/test/lux/macro/syntax.lux index 2d4f771d2..e988a0103 100644 --- a/stdlib/test/test/lux/macro/syntax.lux +++ b/stdlib/test/test/lux/macro/syntax.lux @@ -74,7 +74,7 @@ ["Can parse Nat syntax." +123 code;nat number;Eq<Nat> s;nat] ["Can parse Int syntax." 123 code;int number;Eq<Int> s;int] ["Can parse Deg syntax." .123 code;deg number;Eq<Deg> s;deg] - ["Can parse Real syntax." 123.0 code;real number;Eq<Real> s;real] + ["Can parse Frac syntax." 123.0 code;frac number;Eq<Frac> s;frac] ["Can parse Text syntax." "\n" code;text text;Eq<Text> s;text] ["Can parse Symbol syntax." ["yolo" "lol"] code;symbol ident;Eq<Ident> s;symbol] ["Can parse Tag syntax." ["yolo" "lol"] code;tag ident;Eq<Ident> s;tag] @@ -115,7 +115,7 @@ (match (#;Right 123) (p;run (list (<ctor> (list (code;int 123)))) (<parser> (p;alt s;bool s;int)))) - (fails? (p;run (list (<ctor> (list (code;real 123.0)))) + (fails? (p;run (list (<ctor> (list (code;frac 123.0)))) (<parser> (p;alt s;bool s;int))))))] ["form" s;form code;form] diff --git a/stdlib/test/test/lux/math.lux b/stdlib/test/test/lux/math.lux index f3cdb0666..63a449965 100644 --- a/stdlib/test/test/lux/math.lux +++ b/stdlib/test/test/lux/math.lux @@ -5,7 +5,7 @@ (data [text "Text/" Monoid<Text>] text/format [bool "b/" Eq<Bool>] - [number "r/" Number<Real>] + [number "f/" Number<Frac>] (coll [list "List/" Fold<List> Functor<List>]) [product]) ["R" math/random] @@ -13,17 +13,17 @@ lux/test) (def: (within? margin-of-error standard value) - (-> Real Real Real Bool) - (r.< margin-of-error - (r/abs (r.- standard value)))) + (-> Frac Frac Frac Bool) + (f.< margin-of-error + (f/abs (f.- standard value)))) -## (def: margin Real 0.0000001) +## (def: margin Frac 0.0000001) ## ## The JVM trigonometry functions sometimes give me funky results. ## ## I won't be testing this, until I can figure out what's going on, or ## ## come up with my own implementation ## (context: "Trigonometry" -## [angle (|> R;real (:: @ map (r.* &;tau)))] +## [angle (|> R;frac (:: @ map (f.* &;tau)))] ## ($_ seq ## (test "Sine and arc-sine are inverse functions." ## (|> angle &;sin &;asin (within? margin angle))) @@ -39,39 +39,39 @@ [factor (|> R;nat (:: @ map (|>. (n.% +1000) (n.max +1) nat-to-int - int-to-real))) - base (|> R;real (:: @ map (r.* factor)))] + int-to-frac))) + base (|> R;frac (:: @ map (f.* factor)))] ($_ seq (test "Square-root is inverse of square." - (|> base (&;pow 2.0) &;root2 (r.= base))) + (|> base (&;pow 2.0) &;root2 (f.= base))) (test "Cubic-root is inverse of cube." - (|> base (&;pow 3.0) &;root3 (r.= base))) + (|> base (&;pow 3.0) &;root3 (f.= base))) )) (context: "Rounding" - [sample (|> R;real (:: @ map (r.* 1000.0)))] + [sample (|> R;frac (:: @ map (f.* 1000.0)))] ($_ seq (test "The ceiling will be an integer value, and will be >= the original." (let [ceil'd (&;ceil sample)] - (and (|> ceil'd real-to-int int-to-real (r.= ceil'd)) - (r.>= sample ceil'd) - (r.<= 1.0 (r.- sample ceil'd))))) + (and (|> ceil'd frac-to-int int-to-frac (f.= ceil'd)) + (f.>= sample ceil'd) + (f.<= 1.0 (f.- sample ceil'd))))) (test "The floor will be an integer value, and will be <= the original." (let [floor'd (&;floor sample)] - (and (|> floor'd real-to-int int-to-real (r.= floor'd)) - (r.<= sample floor'd) - (r.<= 1.0 (r.- floor'd sample))))) + (and (|> floor'd frac-to-int int-to-frac (f.= floor'd)) + (f.<= sample floor'd) + (f.<= 1.0 (f.- floor'd sample))))) (test "The round will be an integer value, and will be < or > or = the original." (let [round'd (&;round sample)] - (and (|> round'd real-to-int int-to-real (r.= round'd)) - (r.<= 1.0 (r/abs (r.- sample round'd)))))) + (and (|> round'd frac-to-int int-to-frac (f.= round'd)) + (f.<= 1.0 (f/abs (f.- sample round'd)))))) )) (context: "Exponentials and logarithms" - [sample (|> R;real (:: @ map (r.* 10.0)))] + [sample (|> R;frac (:: @ map (f.* 10.0)))] (test "Logarithm is the inverse of exponential." (|> sample &;exp &;log (within? 1.0e-15 sample)))) diff --git a/stdlib/test/test/lux/math/logic/fuzzy.lux b/stdlib/test/test/lux/math/logic/fuzzy.lux index bb27a435d..5f10696c1 100644 --- a/stdlib/test/test/lux/math/logic/fuzzy.lux +++ b/stdlib/test/test/lux/math/logic/fuzzy.lux @@ -48,7 +48,7 @@ (<gte> top sample)))) ))] - ["Real" number;Hash<Real> R;real &;r.triangle r.< r.<= r.> r.>=] + ["Frac" number;Hash<Frac> R;frac &;f.triangle f.< f.<= f.> f.>=] ["Deg" number;Hash<Deg> R;deg &;d.triangle d.< d.<= d.> d.>=] ) @@ -94,29 +94,29 @@ (<gte> top sample)))) ))] - ["Real" number;Hash<Real> R;real &;r.trapezoid r.< r.<= r.> r.>=] + ["Frac" number;Hash<Frac> R;frac &;f.trapezoid f.< f.<= f.> f.>=] ["Deg" number;Hash<Deg> R;deg &;d.trapezoid d.< d.<= d.> d.>=] ) (context: "Gaussian" - [deviation (|> R;real (R;filter (r.> 0.0))) - center R;real + [deviation (|> R;frac (R;filter (f.> 0.0))) + center R;frac #let [gaussian (&;gaussian deviation center)]] (test "The center value will always have maximum membership." (d.= ~true (&;membership center gaussian)))) (def: gen-triangle - (R;Random (&;Fuzzy Real)) + (R;Random (&;Fuzzy Frac)) (do R;Monad<Random> - [x R;real - y R;real - z R;real] - (wrap (&;r.triangle x y z)))) + [x R;frac + y R;frac + z R;frac] + (wrap (&;f.triangle x y z)))) (context: "Combinators" [left gen-triangle right gen-triangle - sample R;real] + sample R;frac] ($_ seq (test "Union membership as as high as membership in any of its members." (let [combined (&;union left right) @@ -162,7 +162,7 @@ (context: "Thresholds" [fuzzy gen-triangle - sample R;real + sample R;frac threshold R;deg #let [vip-fuzzy (&;cut threshold fuzzy) member? (&;to-predicate threshold fuzzy)]] |