diff options
author | Eduardo Julian | 2020-12-01 09:27:58 -0400 |
---|---|---|
committer | Eduardo Julian | 2020-12-01 09:27:58 -0400 |
commit | cfa0a075b89a0df4618e7009f05c157393cbba72 (patch) | |
tree | 4bb658a44cfade42e27f9f6bf87d7118c69af6e0 /stdlib/source/lux/abstract | |
parent | 7444deb1b80d469280fcb0684d91c13f752a86d6 (diff) |
Added specialized root/2 and root/3 functions in lux/math.
Diffstat (limited to '')
-rw-r--r-- | stdlib/source/lux/abstract/enum.lux | 12 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/fold.lux | 4 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/functor.lux | 16 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/interval.lux | 78 | ||||
-rw-r--r-- | stdlib/source/lux/abstract/monad.lux | 42 |
5 files changed, 76 insertions, 76 deletions
diff --git a/stdlib/source/lux/abstract/enum.lux b/stdlib/source/lux/abstract/enum.lux index ce9b66d92..0c099feb2 100644 --- a/stdlib/source/lux/abstract/enum.lux +++ b/stdlib/source/lux/abstract/enum.lux @@ -12,14 +12,14 @@ (def: #export (range enum from to) {#.doc "An inclusive [from, to] range of values."} (All [a] (-> (Enum a) a a (List a))) - (let [(^open "/@.") enum] + (let [(^open "/\.") enum] (loop [end to output #.Nil] - (cond (/@< end from) - (recur (/@pred end) (#.Cons end output)) + (cond (/\< end from) + (recur (/\pred end) (#.Cons end output)) - (/@< from end) - (recur (/@succ end) (#.Cons end output)) + (/\< from end) + (recur (/\succ end) (#.Cons end output)) - ## (/@= end from) + ## (/\= end from) (#.Cons end output))))) diff --git a/stdlib/source/lux/abstract/fold.lux b/stdlib/source/lux/abstract/fold.lux index a63dc8e20..fd309b5f0 100644 --- a/stdlib/source/lux/abstract/fold.lux +++ b/stdlib/source/lux/abstract/fold.lux @@ -12,5 +12,5 @@ (def: #export (with-monoid monoid fold value) (All [F a] (-> (Monoid a) (Fold F) (F a) a)) - (let [(^open "/@.") monoid] - (fold /@compose /@identity value))) + (let [(^open "/\.") monoid] + (fold /\compose /\identity value))) diff --git a/stdlib/source/lux/abstract/functor.lux b/stdlib/source/lux/abstract/functor.lux index 9ba47aaf8..03c10eaaf 100644 --- a/stdlib/source/lux/abstract/functor.lux +++ b/stdlib/source/lux/abstract/functor.lux @@ -12,33 +12,33 @@ (type: #export (Or f g) (All [a] (| (f a) (g a)))) -(def: #export (sum (^open "f@.") (^open "g@.")) +(def: #export (sum (^open "f\.") (^open "g\.")) (All [F G] (-> (Functor F) (Functor G) (Functor (..Or F G)))) (structure (def: (map f fa|ga) (case fa|ga (#.Left fa) - (#.Left (f@map f fa)) + (#.Left (f\map f fa)) (#.Right ga) - (#.Right (g@map f ga)))))) + (#.Right (g\map f ga)))))) (type: #export (And f g) (All [a] (& (f a) (g a)))) -(def: #export (product (^open "f@.") (^open "g@.")) +(def: #export (product (^open "f\.") (^open "g\.")) (All [F G] (-> (Functor F) (Functor G) (Functor (..And F G)))) (structure (def: (map f [fa ga]) - [(f@map f fa) - (g@map f ga)]))) + [(f\map f fa) + (g\map f ga)]))) (type: #export (Then f g) (All [a] (f (g a)))) -(def: #export (compose (^open "f@.") (^open "g@.")) +(def: #export (compose (^open "f\.") (^open "g\.")) {#.doc "Functor composition."} (All [F G] (-> (Functor F) (Functor G) (Functor (..Then F G)))) (structure (def: (map f fga) - (f@map (g@map f) fga)))) + (f\map (g\map f) fga)))) diff --git a/stdlib/source/lux/abstract/interval.lux b/stdlib/source/lux/abstract/interval.lux index 46fe020e1..c429fa5c8 100644 --- a/stdlib/source/lux/abstract/interval.lux +++ b/stdlib/source/lux/abstract/interval.lux @@ -34,28 +34,28 @@ (template [<name> <comp>] [(def: #export (<name> interval) (All [a] (-> (Interval a) Bit)) - (let [(^open ",@.") interval] - (<comp> ,@bottom ,@top)))] + (let [(^open ",\.") interval] + (<comp> ,\bottom ,\top)))] - [inner? (order.> ,@&order)] - [outer? ,@<] - [singleton? ,@=] + [inner? (order.> ,\&order)] + [outer? ,\<] + [singleton? ,\=] ) (def: #export (within? interval elem) (All [a] (-> (Interval a) a Bit)) - (let [(^open ",@.") interval] + (let [(^open ",\.") interval] (cond (inner? interval) - (and (order.>= ,@&order ,@bottom elem) - (order.<= ,@&order ,@top elem)) + (and (order.>= ,\&order ,\bottom elem) + (order.<= ,\&order ,\top elem)) (outer? interval) - (or (order.>= ,@&order ,@bottom elem) - (order.<= ,@&order ,@top elem)) + (or (order.>= ,\&order ,\bottom elem) + (order.<= ,\&order ,\top elem)) ## singleton - (and (,@= ,@bottom elem) - (,@= ,@top elem))))) + (and (,\= ,\bottom elem) + (,\= ,\top elem))))) (template [<name> <limit>] [(def: #export (<name> elem interval) @@ -105,20 +105,20 @@ (template [<name> <comp>] [(def: #export (<name> reference sample) (All [a] (-> a (Interval a) Bit)) - (let [(^open ",@.") sample] - (and (<comp> reference ,@bottom) - (<comp> reference ,@top))))] + (let [(^open ",\.") sample] + (and (<comp> reference ,\bottom) + (<comp> reference ,\top))))] - [before? ,@<] - [after? (order.> ,@&order)] + [before? ,\<] + [after? (order.> ,\&order)] ) (def: #export (meets? reference sample) (All [a] (-> (Interval a) (Interval a) Bit)) - (let [(^open ",@.") reference + (let [(^open ",\.") reference limit (:: reference bottom)] - (and (,@= limit (:: sample top)) - (order.<= ,@&order limit (:: sample bottom))))) + (and (,\= limit (:: sample top)) + (order.<= ,\&order limit (:: sample bottom))))) (def: #export (touches? reference sample) (All [a] (-> (Interval a) (Interval a) Bit)) @@ -128,47 +128,47 @@ (template [<name> <eq-side> <ineq> <ineq-side>] [(def: #export (<name> reference sample) (All [a] (-> (Interval a) (Interval a) Bit)) - (let [(^open ",@.") reference] - (and (,@= (:: reference <eq-side>) + (let [(^open ",\.") reference] + (and (,\= (:: reference <eq-side>) (:: sample <eq-side>)) - (<ineq> ,@&order + (<ineq> ,\&order (:: reference <ineq-side>) (:: sample <ineq-side>)))))] - [starts? ,@bottom order.<= ,@top] - [finishes? ,@top order.>= ,@bottom] + [starts? ,\bottom order.<= ,\top] + [finishes? ,\top order.>= ,\bottom] ) (structure: #export equivalence (All [a] (Equivalence (Interval a))) (def: (= reference sample) - (let [(^open ",@.") reference] - (and (,@= ,@bottom (:: sample bottom)) - (,@= ,@top (:: sample top)))))) + (let [(^open ",\.") reference] + (and (,\= ,\bottom (:: sample bottom)) + (,\= ,\top (:: sample top)))))) (def: #export (nested? reference sample) (All [a] (-> (Interval a) (Interval a) Bit)) (cond (or (singleton? sample) (and (inner? reference) (inner? sample)) (and (outer? reference) (outer? sample))) - (let [(^open ",@.") reference] - (and (order.>= ,@&order (:: reference bottom) (:: sample bottom)) - (order.<= ,@&order (:: reference top) (:: sample top)))) + (let [(^open ",\.") reference] + (and (order.>= ,\&order (:: reference bottom) (:: sample bottom)) + (order.<= ,\&order (:: reference top) (:: sample top)))) (or (singleton? reference) (and (inner? reference) (outer? sample))) #0 ## (and (outer? reference) (inner? sample)) - (let [(^open ",@.") reference] - (or (and (order.>= ,@&order (:: reference bottom) (:: sample bottom)) - (order.> ,@&order (:: reference bottom) (:: sample top))) - (and (,@< (:: reference top) (:: sample bottom)) - (order.<= ,@&order (:: reference top) (:: sample top))))) + (let [(^open ",\.") reference] + (or (and (order.>= ,\&order (:: reference bottom) (:: sample bottom)) + (order.> ,\&order (:: reference bottom) (:: sample top))) + (and (,\< (:: reference top) (:: sample bottom)) + (order.<= ,\&order (:: reference top) (:: sample top))))) )) (def: #export (overlaps? reference sample) (All [a] (-> (Interval a) (Interval a) Bit)) - (let [(^open ",@.") reference] + (let [(^open ",\.") reference] (and (not (:: ..equivalence = reference sample)) (cond (singleton? sample) #0 @@ -178,8 +178,8 @@ (or (and (inner? sample) (outer? reference)) (and (outer? sample) (inner? reference))) - (or (order.>= ,@&order (:: reference bottom) (:: sample top)) - (order.<= ,@&order (:: reference top) (:: sample bottom))) + (or (order.>= ,\&order (:: reference bottom) (:: sample top)) + (order.<= ,\&order (:: reference top) (:: sample bottom))) ## both inner (inner? sample) diff --git a/stdlib/source/lux/abstract/monad.lux b/stdlib/source/lux/abstract/monad.lux index 7cc5ae263..052191e66 100644 --- a/stdlib/source/lux/abstract/monad.lux +++ b/stdlib/source/lux/abstract/monad.lux @@ -5,7 +5,7 @@ [// [functor (#+ Functor)]]) -(def: (list@fold f init xs) +(def: (list\fold f init xs) (All [a b] (-> (-> b a a) a (List b) a)) (case xs @@ -13,9 +13,9 @@ init (#.Cons x xs') - (list@fold f (f x init) xs'))) + (list\fold f (f x init) xs'))) -(def: (list@size xs) +(def: (list\size xs) (All [a] (-> (List a) Nat)) (loop [counter 0 xs xs] @@ -29,7 +29,7 @@ (def: (reverse xs) (All [a] (-> (List a) (List a))) - (list@fold (function (_ head tail) (#.Cons head tail)) + (list\fold (function (_ head tail) (#.Cons head tail)) #.Nil xs)) @@ -69,14 +69,14 @@ _ #.None)) (#.Some [?name monad bindings body]) - (if (|> bindings list@size .int ("lux i64 %" +2) ("lux i64 =" +0)) + (if (|> bindings list\size .int ("lux i64 %" +2) ("lux i64 =" +0)) (let [[module short] (name-of ..do) gensym (: (-> Text Code) (|>> ($_ "lux text concat" module " " short " ") [""] #.Identifier [location.dummy])) g!_ (gensym "_") g!map (gensym "map") g!join (gensym "join") - body' (list@fold (: (-> [Code Code] Code Code) + body' (list\fold (: (-> [Code Code] Code Code) (function (_ binding body') (let [[var value] binding] (case var @@ -118,55 +118,55 @@ (All [M a] (-> (Monad M) (List (M a)) (M (List a)))) - (let [(^open "!@.") monad] + (let [(^open "!\.") monad] (function (recur xs) (case xs #.Nil - (!@wrap #.Nil) + (!\wrap #.Nil) (#.Cons x xs') (|> x - (!@map (function (_ _x) - (!@map (|>> (#.Cons _x)) (recur xs')))) - !@join))))) + (!\map (function (_ _x) + (!\map (|>> (#.Cons _x)) (recur xs')))) + !\join))))) (def: #export (map monad f) {#.doc "Apply a monadic function to all values in a list."} (All [M a b] (-> (Monad M) (-> a (M b)) (List a) (M (List b)))) - (let [(^open "!@.") monad] + (let [(^open "!\.") monad] (function (recur xs) (case xs #.Nil - (!@wrap #.Nil) + (!\wrap #.Nil) (#.Cons x xs') (|> (f x) - (!@map (function (_ _x) - (!@map (|>> (#.Cons _x)) (recur xs')))) - !@join))))) + (!\map (function (_ _x) + (!\map (|>> (#.Cons _x)) (recur xs')))) + !\join))))) (def: #export (filter monad f) {#.doc "Filter the values in a list with a monadic function."} (All [! a b] (-> (Monad !) (-> a (! Bit)) (List a) (! (List a)))) - (let [(^open "!@.") monad] + (let [(^open "!\.") monad] (function (recur xs) (case xs #.Nil - (!@wrap #.Nil) + (!\wrap #.Nil) (#.Cons head xs') (|> (f head) - (!@map (function (_ verdict) - (!@map (function (_ tail) + (!\map (function (_ verdict) + (!\map (function (_ tail) (if verdict (#.Cons head tail) tail)) (recur xs')))) - !@join))))) + !\join))))) (def: #export (fold monad f init xs) {#.doc "Fold a list with a monadic function."} |