aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/macro
diff options
context:
space:
mode:
authorEduardo Julian2018-07-28 13:36:49 -0400
committerEduardo Julian2018-07-28 13:36:49 -0400
commitdff8878c13610ae8d1207aaabefbecc88cd3911f (patch)
tree11f78712c9f1cafd8be3ec67c5bcb1c738c115be /stdlib/source/lux/macro
parentb14102eaa2a80f51f160ba293ec01928dbe683c3 (diff)
Temporary commit to get rid of "+" signs for Nat.
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/macro/code.lux2
-rw-r--r--stdlib/source/lux/macro/poly.lux36
-rw-r--r--stdlib/source/lux/macro/poly/equivalence.lux2
-rw-r--r--stdlib/source/lux/macro/poly/functor.lux8
-rw-r--r--stdlib/source/lux/macro/poly/json.lux10
5 files changed, 29 insertions, 29 deletions
diff --git a/stdlib/source/lux/macro/code.lux b/stdlib/source/lux/macro/code.lux
index f6896343c..0de1e5772 100644
--- a/stdlib/source/lux/macro/code.lux
+++ b/stdlib/source/lux/macro/code.lux
@@ -27,7 +27,7 @@
## (Ann Cursor (Code' (Ann Cursor))))
## [Utils]
-(def: _cursor Cursor ["" +0 +0])
+(def: _cursor Cursor ["" |0 |0])
## [Functions]
(do-template [<name> <type> <tag>]
diff --git a/stdlib/source/lux/macro/poly.lux b/stdlib/source/lux/macro/poly.lux
index 97ec08ff7..9be5a2ad4 100644
--- a/stdlib/source/lux/macro/poly.lux
+++ b/stdlib/source/lux/macro/poly.lux
@@ -153,7 +153,7 @@
(do p.Monad<Parser>
[headT any]
(let [members (<flattener> (type.un-name headT))]
- (if (n/> +1 (list.size members))
+ (if (n/> |1 (list.size members))
(local members poly)
(p.fail (ex.construct <exception> headT))))))]
@@ -166,7 +166,7 @@
(do p.Monad<Parser>
[headT any
#let [[num-arg bodyT] (type.flatten-univ-q (type.un-name headT))]]
- (if (n/= +0 num-arg)
+ (if (n/= |0 num-arg)
(p.fail (ex.construct not-polymorphic headT))
(wrap [num-arg bodyT]))))
@@ -178,22 +178,22 @@
[num-args non-poly] (local (list headT) polymorphic')
env ..env
#let [funcL (label funcI)
- [all-varsL env'] (loop [current-arg +0
+ [all-varsL env'] (loop [current-arg |0
env' env
all-varsL (: (List Code) (list))]
(if (n/< num-args current-arg)
- (if (n/= +0 current-arg)
+ (if (n/= |0 current-arg)
(let [varL (label (inc funcI))]
(recur (inc current-arg)
(|> env'
(dict.put funcI [headT funcL])
(dict.put (inc funcI) [(#.Parameter (inc funcI)) varL]))
(#.Cons varL all-varsL)))
- (let [partialI (|> current-arg (n/* +2) (n/+ funcI))
+ (let [partialI (|> current-arg (n/* |2) (n/+ funcI))
partial-varI (inc partialI)
partial-varL (label partial-varI)
- partialC (` ((~ funcL) (~+ (|> (list.n/range +0 (dec num-args))
- (list/map (|>> (n/* +2) inc (n/+ funcI) label))
+ partialC (` ((~ funcL) (~+ (|> (list.n/range |0 (dec num-args))
+ (list/map (|>> (n/* |2) inc (n/+ funcI) label))
list.reverse))))]
(recur (inc current-arg)
(|> env'
@@ -212,7 +212,7 @@
(do p.Monad<Parser>
[headT any
#let [[inputsT outputT] (type.flatten-function (type.un-name headT))]]
- (if (n/> +0 (list.size inputsT))
+ (if (n/> |0 (list.size inputsT))
(p.and (local inputsT in-poly)
(local (list outputT) out-poly))
(p.fail (ex.construct not-function headT)))))
@@ -222,7 +222,7 @@
(do p.Monad<Parser>
[headT any
#let [[funcT paramsT] (type.flatten-application (type.un-name headT))]]
- (if (n/= +0 (list.size paramsT))
+ (if (n/= |0 (list.size paramsT))
(p.fail (ex.construct not-application headT))
(local (#.Cons funcT paramsT) poly))))
@@ -242,10 +242,10 @@
(def: (adjusted-idx env idx)
(-> Env Nat Nat)
- (let [env-level (n// +2 (dict.size env))
- parameter-level (n// +2 idx)
- parameter-idx (n/% +2 idx)]
- (|> env-level dec (n/- parameter-level) (n/* +2) (n/+ parameter-idx))))
+ (let [env-level (n// |2 (dict.size env))
+ parameter-level (n// |2 idx)
+ parameter-idx (n/% |2 idx)]
+ (|> env-level dec (n/- parameter-level) (n/* |2) (n/+ parameter-idx))))
(def: #export parameter
(Poly Code)
@@ -323,8 +323,8 @@
headT any]
(case (type.un-name headT)
(^multi (#.Apply (#.Named ["lux" "Nothing"] _) (#.Parameter funcT-idx))
- (n/= +0 (adjusted-idx env funcT-idx))
- [(dict.get +0 env) (#.Some [self-type self-call])])
+ (n/= |0 (adjusted-idx env funcT-idx))
+ [(dict.get |0 env) (#.Some [self-type self-call])])
(wrap self-call)
_
@@ -335,7 +335,7 @@
(do p.Monad<Parser>
[env ..env
[funcT argsT] (apply (p.and any (p.many any)))
- _ (local (list funcT) (..parameter! +0))
+ _ (local (list funcT) (..parameter! |0))
allC (let [allT (list& funcT argsT)]
(|> allT
(monad.map @ (function.constant ..parameter))
@@ -425,13 +425,13 @@
(#.Parameter idx)
(let [idx (adjusted-idx env idx)]
- (if (n/= +0 idx)
+ (if (n/= |0 idx)
(|> (dict.get idx env) maybe.assume product.left (to-code env))
(` (.$ (~ (code.nat (dec idx)))))))
(#.Apply (#.Named ["lux" "Nothing"] _) (#.Parameter idx))
(let [idx (adjusted-idx env idx)]
- (if (n/= +0 idx)
+ (if (n/= |0 idx)
(|> (dict.get idx env) maybe.assume product.left (to-code env))
(undefined)))
diff --git a/stdlib/source/lux/macro/poly/equivalence.lux b/stdlib/source/lux/macro/poly/equivalence.lux
index cb9280506..6f356c060 100644
--- a/stdlib/source/lux/macro/poly/equivalence.lux
+++ b/stdlib/source/lux/macro/poly/equivalence.lux
@@ -116,7 +116,7 @@
(do @
[g!eqs (poly.tuple (p.many Equivalence<?>))
#let [g!_ (code.local-identifier "_____________")
- indices (|> (list.size g!eqs) dec (list.n/range +0))
+ indices (|> (list.size g!eqs) dec (list.n/range |0))
g!lefts (list/map (|>> nat/encode (text/compose "left") code.local-identifier) indices)
g!rights (list/map (|>> nat/encode (text/compose "right") code.local-identifier) indices)]]
(wrap (` (: (~ (@Equivalence inputT))
diff --git a/stdlib/source/lux/macro/poly/functor.lux b/stdlib/source/lux/macro/poly/functor.lux
index d28e98337..711179404 100644
--- a/stdlib/source/lux/macro/poly/functor.lux
+++ b/stdlib/source/lux/macro/poly/functor.lux
@@ -29,7 +29,7 @@
#let [num-vars (list.size varsC)]
#let [@Functor (: (-> Type Code)
(function (_ unwrappedT)
- (if (n/= +1 num-vars)
+ (if (n/= |1 num-vars)
(` ((~! functor.Functor) (~ (poly.to-code *env* unwrappedT))))
(let [paramsC (|> num-vars dec list.indices (list/map (|>> %n code.local-identifier)))]
(` (All [(~+ paramsC)]
@@ -39,7 +39,7 @@
($_ p.either
## Type-var
(do p.Monad<Parser>
- [#let [varI (|> num-vars (n/* +2) dec)]
+ [#let [varI (|> num-vars (n/* |2) dec)]
_ (poly.parameter! varI)]
(wrap (` ((~ funcC) (~ valueC)))))
## Variants
@@ -54,7 +54,7 @@
## Tuples
(do p.Monad<Parser>
[pairsCC (: (poly.Poly (List [Code Code]))
- (poly.tuple (loop [idx +0
+ (poly.tuple (loop [idx |0
pairsCC (: (List [Code Code])
(list))]
(p.either (let [slotC (|> idx %n (format "____________slot") code.local-identifier)]
@@ -75,7 +75,7 @@
[inT+ outC] (poly.function (p.many poly.any)
(Arg<?> outL))
#let [inC+ (|> (list.size inT+) dec
- (list.n/range +0)
+ (list.n/range |0)
(list/map (|>> %n (format "____________inC") code.local-identifier)))]]
(wrap (` (function ((~ g!) (~+ inC+))
(let [(~ outL) ((~ valueC) (~+ inC+))]
diff --git a/stdlib/source/lux/macro/poly/json.lux b/stdlib/source/lux/macro/poly/json.lux
index 31ae2fdff..b9710773a 100644
--- a/stdlib/source/lux/macro/poly/json.lux
+++ b/stdlib/source/lux/macro/poly/json.lux
@@ -44,12 +44,12 @@
(function (_ input)
(non-rec (rec-encode non-rec) input)))
-(def: low-mask Nat (|> +1 (i64.left-shift +32) dec))
-(def: high-mask Nat (|> low-mask (i64.left-shift +32)))
+(def: low-mask Nat (|> |1 (i64.left-shift |32) dec))
+(def: high-mask Nat (|> low-mask (i64.left-shift |32)))
(structure: _ (Codec JSON Nat)
(def: (encode input)
- (let [high (|> input (i64.and high-mask) (i64.logical-right-shift +32))
+ (let [high (|> input (i64.and high-mask) (i64.logical-right-shift |32))
low (i64.and low-mask input)]
(#//.Array (row (|> high .int int-to-frac #//.Number)
(|> low .int int-to-frac #//.Number)))))
@@ -59,7 +59,7 @@
(do p.Monad<Parser>
[high //.number
low //.number])
- (wrap (n/+ (|> high frac-to-int .nat (i64.left-shift +32))
+ (wrap (n/+ (|> high frac-to-int .nat (i64.left-shift |32))
(|> low frac-to-int .nat))))))
(structure: _ (Codec JSON Int)
@@ -164,7 +164,7 @@
[g!encoders (poly.tuple (p.many Codec<JSON,?>//encode))
#let [g!_ (code.local-identifier "_______")
g!members (|> (list.size g!encoders) dec
- (list.n/range +0)
+ (list.n/range |0)
(list/map (|>> nat/encode code.local-identifier)))]]
(wrap (` (: (~ (@JSON//encode inputT))
(function ((~ g!_) [(~+ g!members)])