aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/control
diff options
context:
space:
mode:
authorEduardo Julian2017-11-27 02:09:04 -0400
committerEduardo Julian2017-11-27 02:09:04 -0400
commitd6a7a133c5c4a734ab45e9497c8e5df749ce383a (patch)
tree040b4df12dd3482fc0bb76f8e0a37126ef34fb34 /stdlib/source/lux/control
parent6031fc715b4a16b008d6f288c38739d9bb066490 (diff)
- Changed the prefixes of numeric functions.
Diffstat (limited to 'stdlib/source/lux/control')
-rw-r--r--stdlib/source/lux/control/comonad.lux6
-rw-r--r--stdlib/source/lux/control/concatenative.lux96
-rw-r--r--stdlib/source/lux/control/contract.lux6
-rw-r--r--stdlib/source/lux/control/monad.lux4
-rw-r--r--stdlib/source/lux/control/parser.lux10
-rw-r--r--stdlib/source/lux/control/pipe.lux28
6 files changed, 75 insertions, 75 deletions
diff --git a/stdlib/source/lux/control/comonad.lux b/stdlib/source/lux/control/comonad.lux
index 15625b8f1..dd395ff64 100644
--- a/stdlib/source/lux/control/comonad.lux
+++ b/stdlib/source/lux/control/comonad.lux
@@ -27,13 +27,13 @@
(macro: #export (be tokens state)
{#;doc (doc "A co-monadic parallel to the \"do\" macro."
- (let [square (function [n] (i.* n n))]
+ (let [square (function [n] (i/* n n))]
(be CoMonad<Stream>
- [inputs (iterate i.inc 2)]
+ [inputs (iterate i/inc 2)]
(square (head inputs)))))}
(case tokens
(#;Cons comonad (#;Cons [_ (#;Tuple bindings)] (#;Cons body #;Nil)))
- (if (|> bindings list;size (n.% +2) (n.= +0))
+ (if (|> bindings list;size (n/% +2) (n/= +0))
(let [g!map (: Code [_cursor (#;Symbol ["" " map "])])
g!split (: Code [_cursor (#;Symbol ["" " split "])])
body' (list/fold (: (-> [Code Code] Code Code)
diff --git a/stdlib/source/lux/control/concatenative.lux b/stdlib/source/lux/control/concatenative.lux
index b0ed0f585..ef66ffac8 100644
--- a/stdlib/source/lux/control/concatenative.lux
+++ b/stdlib/source/lux/control/concatenative.lux
@@ -1,8 +1,8 @@
(;module: [lux #- if loop when
- n.+ n.- n.* n./ n.% n.= n.< n.<= n.> n.>=
- i.+ i.- i.* i./ i.% i.= i.< i.<= i.> i.>=
- d.+ d.- d.* d./ d.% d.= d.< d.<= d.> d.>=
- f.+ f.- f.* f./ f.% f.= f.< f.<= f.> f.>=]
+ n/+ n/- n/* n// n/% n/= n/< n/<= n/> n/>=
+ i/+ i/- i/* i// i/% i/= i/< i/<= i/> i/>=
+ d/+ d/- d/* d// d/% d/= d/< d/<= d/> d/>=
+ f/+ f/- f/* f// f/% f/= f/< f/<= f/> f/>=]
(lux (control ["p" parser "p/" Monad<Parser>]
[monad])
(data [text]
@@ -121,7 +121,7 @@
(~ type)
(|>. (~@ (L/map prepare commands))))))))
-(syntax: #export (apply [arity (|> s;nat (p;filter (;n.> +0)))])
+(syntax: #export (apply [arity (|> s;nat (p;filter (;n/> +0)))])
(with-gensyms [g!func g!stack g!output]
(monad;do @
[g!inputs (|> (macro;gensym "input") (list;repeat arity) (monad;seq @))]
@@ -198,49 +198,49 @@
(function [[[stack subject] param]]
[stack (<func> param subject)]))]
- [Nat Nat n.+ ;n.+]
- [Nat Nat n.- ;n.-]
- [Nat Nat n.* ;n.*]
- [Nat Nat n./ ;n./]
- [Nat Nat n.% ;n.%]
- [Nat Bool n.= ;n.=]
- [Nat Bool n.< ;n.<]
- [Nat Bool n.<= ;n.<=]
- [Nat Bool n.> ;n.>]
- [Nat Bool n.>= ;n.>=]
-
- [Int Int i.+ ;i.+]
- [Int Int i.- ;i.-]
- [Int Int i.* ;i.*]
- [Int Int i./ ;i./]
- [Int Int i.% ;i.%]
- [Int Bool i.= ;i.=]
- [Int Bool i.< ;i.<]
- [Int Bool i.<= ;i.<=]
- [Int Bool i.> ;i.>]
- [Int Bool i.>= ;i.>=]
-
- [Deg Deg d.+ ;d.+]
- [Deg Deg d.- ;d.-]
- [Deg Deg d.* ;d.*]
- [Deg Deg d./ ;d./]
- [Deg Deg d.% ;d.%]
- [Deg Bool d.= ;d.=]
- [Deg Bool d.< ;d.<]
- [Deg Bool d.<= ;d.<=]
- [Deg Bool d.> ;d.>]
- [Deg Bool d.>= ;d.>=]
-
- [Frac Frac f.+ ;f.+]
- [Frac Frac f.- ;f.-]
- [Frac Frac f.* ;f.*]
- [Frac Frac f./ ;f./]
- [Frac Frac f.% ;f.%]
- [Frac Bool f.= ;f.=]
- [Frac Bool f.< ;f.<]
- [Frac Bool f.<= ;f.<=]
- [Frac Bool f.> ;f.>]
- [Frac Bool f.>= ;f.>=]
+ [Nat Nat n/+ ;n/+]
+ [Nat Nat n/- ;n/-]
+ [Nat Nat n/* ;n/*]
+ [Nat Nat n// ;n//]
+ [Nat Nat n/% ;n/%]
+ [Nat Bool n/= ;n/=]
+ [Nat Bool n/< ;n/<]
+ [Nat Bool n/<= ;n/<=]
+ [Nat Bool n/> ;n/>]
+ [Nat Bool n/>= ;n/>=]
+
+ [Int Int i/+ ;i/+]
+ [Int Int i/- ;i/-]
+ [Int Int i/* ;i/*]
+ [Int Int i// ;i//]
+ [Int Int i/% ;i/%]
+ [Int Bool i/= ;i/=]
+ [Int Bool i/< ;i/<]
+ [Int Bool i/<= ;i/<=]
+ [Int Bool i/> ;i/>]
+ [Int Bool i/>= ;i/>=]
+
+ [Deg Deg d/+ ;d/+]
+ [Deg Deg d/- ;d/-]
+ [Deg Deg d/* ;d/*]
+ [Deg Deg d// ;d//]
+ [Deg Deg d/% ;d/%]
+ [Deg Bool d/= ;d/=]
+ [Deg Bool d/< ;d/<]
+ [Deg Bool d/<= ;d/<=]
+ [Deg Bool d/> ;d/>]
+ [Deg Bool d/>= ;d/>=]
+
+ [Frac Frac f/+ ;f/+]
+ [Frac Frac f/- ;f/-]
+ [Frac Frac f/* ;f/*]
+ [Frac Frac f// ;f//]
+ [Frac Frac f/% ;f/%]
+ [Frac Bool f/= ;f/=]
+ [Frac Bool f/< ;f/<]
+ [Frac Bool f/<= ;f/<=]
+ [Frac Bool f/> ;f/>]
+ [Frac Bool f/>= ;f/>=]
)
(def: #export if
diff --git a/stdlib/source/lux/control/contract.lux b/stdlib/source/lux/control/contract.lux
index cc3267715..3b072caa8 100644
--- a/stdlib/source/lux/control/contract.lux
+++ b/stdlib/source/lux/control/contract.lux
@@ -16,7 +16,7 @@
{#;doc (doc "Pre-conditions."
"Given a test and an expression to run, only runs the expression if the test passes."
"Otherwise, an error is raised."
- (pre (i.= 4 (i.+ 2 2))
+ (pre (i/= 4 (i/+ 2 2))
(foo 123 456 789)))}
(wrap (list (` (exec (assert! (~ (code;text (format "Pre-condition failed: " (%code test))))
(~ test))
@@ -27,8 +27,8 @@
"Given a predicate and an expression to run, evaluates the expression and then tests the output with the predicate."
"If the predicate returns true, returns the value of the expression."
"Otherwise, an error is raised."
- (post i.even?
- (i.+ 2 2)))}
+ (post i/even?
+ (i/+ 2 2)))}
(do @
[g!output (macro;gensym "")]
(wrap (list (` (let [(~ g!output) (~ expr)]
diff --git a/stdlib/source/lux/control/monad.lux b/stdlib/source/lux/control/monad.lux
index fb900d3e7..e4495cc92 100644
--- a/stdlib/source/lux/control/monad.lux
+++ b/stdlib/source/lux/control/monad.lux
@@ -23,7 +23,7 @@
counter
(#;Cons _ xs')
- (recur (n.inc counter) xs'))))
+ (recur (n/inc counter) xs'))))
(def: (reverse xs)
(All [a]
@@ -60,7 +60,7 @@
(wrap (f3 z))))}
(case tokens
(#;Cons monad (#;Cons [_ (#;Tuple bindings)] (#;Cons body #;Nil)))
- (if (|> bindings list/size (n.% +2) (n.= +0))
+ (if (|> bindings list/size (n/% +2) (n/= +0))
(let [g!map (: Code [_cursor (#;Symbol ["" " map "])])
g!join (: Code [_cursor (#;Symbol ["" " join "])])
g!apply (: Code [_cursor (#;Symbol ["" " apply "])])
diff --git a/stdlib/source/lux/control/parser.lux b/stdlib/source/lux/control/parser.lux
index 1b91a0248..095104f09 100644
--- a/stdlib/source/lux/control/parser.lux
+++ b/stdlib/source/lux/control/parser.lux
@@ -136,10 +136,10 @@
(def: #export (exactly n p)
{#;doc "Parse exactly N times."}
(All [s a] (-> Nat (Parser s a) (Parser s (List a))))
- (if (n.> +0 n)
+ (if (n/> +0 n)
(do Monad<Parser>
[x p
- xs (exactly (n.dec n) p)]
+ xs (exactly (n/dec n) p)]
(wrap (#;Cons x xs)))
(:: Monad<Parser> wrap (list))))
@@ -154,7 +154,7 @@
(def: #export (at-most n p)
{#;doc "Parse at most N times."}
(All [s a] (-> Nat (Parser s a) (Parser s (List a))))
- (if (n.> +0 n)
+ (if (n/> +0 n)
(function [input]
(case (p input)
(#e;Error msg)
@@ -163,7 +163,7 @@
(#e;Success [input' x])
(run input'
(do Monad<Parser>
- [xs (at-most (n.dec n) p)]
+ [xs (at-most (n/dec n) p)]
(wrap (#;Cons x xs))))
))
(:: Monad<Parser> wrap (list))))
@@ -173,7 +173,7 @@
(All [s a] (-> Nat Nat (Parser s a) (Parser s (List a))))
(do Monad<Parser>
[min-xs (exactly from p)
- max-xs (at-most (n.- from to) p)]
+ max-xs (at-most (n/- from to) p)]
(wrap (:: list;Monad<List> join (list min-xs max-xs)))))
(def: #export (sep-by sep p)
diff --git a/stdlib/source/lux/control/pipe.lux b/stdlib/source/lux/control/pipe.lux
index 6eb8e8156..9903986f7 100644
--- a/stdlib/source/lux/control/pipe.lux
+++ b/stdlib/source/lux/control/pipe.lux
@@ -16,9 +16,9 @@
(syntax: #export (new> [tokens (p;at-least +2 s;any)])
{#;doc (doc "Ignores the piped argument, and begins a new pipe."
(|> 20
- (i.* 3)
- (i.+ 4)
- (new> 0 i.inc)))}
+ (i/* 3)
+ (i/+ 4)
+ (new> 0 i/inc)))}
(case (list;reverse tokens)
(^ (list& _ r-body))
(wrap (list (` (|> (~@ (list;reverse r-body))))))
@@ -29,7 +29,7 @@
(syntax: #export (let> binding body prev)
{#;doc (doc "Gives a name to the piped-argument, within the given expression."
(|> 5
- (let> X (i.+ X X))))}
+ (let> X (i/+ X X))))}
(wrap (list (` (let [(~ binding) (~ prev)]
(~ body))))))
@@ -40,8 +40,8 @@
"Both the tests and the bodies are piped-code, and must be given inside a tuple."
"If a last else-pipe is not given, the piped-argument will be used instead."
(|> 5
- (cond> [i.even?] [(i.* 2)]
- [i.odd?] [(i.* 3)]
+ (cond> [i/even?] [(i/* 2)]
+ [i/odd?] [(i/* 3)]
[(new> -1)])))}
(with-gensyms [g!temp]
(wrap (list (` (with-expansions
@@ -61,8 +61,8 @@
{#;doc (doc "Loops for pipes."
"Both the testing and calculating steps are pipes and must be given inside tuples."
(|> 1
- (loop> [(i.< 10)]
- [i.inc])))}
+ (loop> [(i/< 10)]
+ [i/inc])))}
(with-gensyms [g!temp]
(wrap (list (` (loop [(~ g!temp) (~ prev)]
(if (|> (~ g!temp) (~@ test))
@@ -74,9 +74,9 @@
"Each steps in the monadic computation is a pipe and must be given inside a tuple."
(|> 5
(do> Monad<Identity>
- [(i.* 3)]
- [(i.+ 4)]
- [i.inc])))}
+ [(i/* 3)]
+ [(i/+ 4)]
+ [i/inc])))}
(with-gensyms [g!temp]
(case (list;reverse steps)
(^ (list& last-step prev-steps))
@@ -96,7 +96,7 @@
"Will generate piped computations, but their results will not be used in the larger scope."
(|> 5
(exec> [int-to-nat %n log!])
- (i.* 10)))}
+ (i/* 10)))}
(do @
[g!temp (macro;gensym "")]
(wrap (list (` (let [(~ g!temp) (~ prev)]
@@ -107,8 +107,8 @@
{#;doc (doc "Parallel branching for pipes."
"Allows to run multiple pipelines for a value and gives you a tuple of the outputs."
(|> 5
- (tuple> [(i.* 10)]
- [i.dec (i./ 2)]
+ (tuple> [(i/* 10)]
+ [i/dec (i// 2)]
[Int/encode]))
"Will become: [50 2 \"5\"]")}
(do @