aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/abstract
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/abstract/apply.lux14
-rw-r--r--stdlib/source/lux/abstract/codec.lux8
-rw-r--r--stdlib/source/lux/abstract/comonad/cofree.lux4
-rw-r--r--stdlib/source/lux/abstract/equivalence.lux10
-rw-r--r--stdlib/source/lux/abstract/hash.lux16
-rw-r--r--stdlib/source/lux/abstract/interval.lux50
-rw-r--r--stdlib/source/lux/abstract/monad.lux6
-rw-r--r--stdlib/source/lux/abstract/monad/free.lux20
-rw-r--r--stdlib/source/lux/abstract/monad/indexed.lux8
-rw-r--r--stdlib/source/lux/abstract/monoid.lux6
-rw-r--r--stdlib/source/lux/abstract/order.lux18
11 files changed, 80 insertions, 80 deletions
diff --git a/stdlib/source/lux/abstract/apply.lux b/stdlib/source/lux/abstract/apply.lux
index febf31a73..21d3fb2df 100644
--- a/stdlib/source/lux/abstract/apply.lux
+++ b/stdlib/source/lux/abstract/apply.lux
@@ -23,14 +23,14 @@
(def: (apply fgf fgx)
## TODO: Switch from this version to the one below (in comments) ASAP.
- (let [fgf' (:: f-apply apply
- (:: f-monad wrap (:: g-apply apply))
- fgf)]
- (:: f-apply apply fgf' fgx))
- ## (let [applyF (:: f-apply apply)
- ## applyG (:: g-apply apply)]
+ (let [fgf' (\ f-apply apply
+ (\ f-monad wrap (\ g-apply apply))
+ fgf)]
+ (\ f-apply apply fgf' fgx))
+ ## (let [applyF (\ f-apply apply)
+ ## applyG (\ g-apply apply)]
## ($_ applyF
- ## (:: f-monad wrap applyG)
+ ## (\ f-monad wrap applyG)
## fgf
## fgx))
))
diff --git a/stdlib/source/lux/abstract/codec.lux b/stdlib/source/lux/abstract/codec.lux
index 2a5048cf3..ad59ce450 100644
--- a/stdlib/source/lux/abstract/codec.lux
+++ b/stdlib/source/lux/abstract/codec.lux
@@ -19,10 +19,10 @@
(-> (Codec c b) (Codec b a)
(Codec c a)))
(def: encode
- (|>> (:: ba-codec encode)
- (:: cb-codec encode)))
+ (|>> (\ ba-codec encode)
+ (\ cb-codec encode)))
(def: (decode cy)
(do try.monad
- [by (:: cb-codec decode cy)]
- (:: ba-codec decode by))))
+ [by (\ cb-codec decode cy)]
+ (\ ba-codec decode by))))
diff --git a/stdlib/source/lux/abstract/comonad/cofree.lux b/stdlib/source/lux/abstract/comonad/cofree.lux
index eadfa788f..8e43cd9bf 100644
--- a/stdlib/source/lux/abstract/comonad/cofree.lux
+++ b/stdlib/source/lux/abstract/comonad/cofree.lux
@@ -12,7 +12,7 @@
(All [F] (-> (Functor F) (Functor (CoFree F))))
(def: (map f [head tail])
- [(f head) (:: dsl map (map f) tail)]))
+ [(f head) (\ dsl map (map f) tail)]))
(structure: #export (comonad dsl)
(All [F] (-> (Functor F) (CoMonad (CoFree F))))
@@ -24,4 +24,4 @@
(def: (split [head tail])
[[head tail]
- (:: dsl map split tail)]))
+ (\ dsl map split tail)]))
diff --git a/stdlib/source/lux/abstract/equivalence.lux b/stdlib/source/lux/abstract/equivalence.lux
index d65e101a8..a467f0b50 100644
--- a/stdlib/source/lux/abstract/equivalence.lux
+++ b/stdlib/source/lux/abstract/equivalence.lux
@@ -15,10 +15,10 @@
(def: (= reference sample)
(case [reference sample]
[(#.Left reference) (#.Left sample)]
- (:: left = reference sample)
+ (\ left = reference sample)
[(#.Right reference) (#.Right sample)]
- (:: right = reference sample)
+ (\ right = reference sample)
_
false))))
@@ -27,8 +27,8 @@
(All [l r] (-> (Equivalence l) (Equivalence r) (Equivalence [l r])))
(structure
(def: (= [a b] [x y])
- (and (:: left = a x)
- (:: right = b y)))))
+ (and (\ left = a x)
+ (\ right = b y)))))
(def: #export (rec sub)
(All [a] (-> (-> (Equivalence a) (Equivalence a)) (Equivalence a)))
@@ -42,4 +42,4 @@
(def: (map f equivalence)
(structure
(def: (= reference sample)
- (:: equivalence = (f reference) (f sample))))))
+ (\ equivalence = (f reference) (f sample))))))
diff --git a/stdlib/source/lux/abstract/hash.lux b/stdlib/source/lux/abstract/hash.lux
index df2dd2e27..f22bdc62a 100644
--- a/stdlib/source/lux/abstract/hash.lux
+++ b/stdlib/source/lux/abstract/hash.lux
@@ -15,25 +15,25 @@
(All [l r] (-> (Hash l) (Hash r) (Hash (| l r))))
(structure
(def: &equivalence
- (equivalence.sum (:: left &equivalence)
- (:: right &equivalence)))
+ (equivalence.sum (\ left &equivalence)
+ (\ right &equivalence)))
(def: (hash value)
(<| (:coerce Nat)
(case value
(#.Left value)
- ("lux i64 *" +2 (:coerce Int (:: left hash value)))
+ ("lux i64 *" +2 (:coerce Int (\ left hash value)))
(#.Right value)
- ("lux i64 *" +3 (:coerce Int (:: right hash value))))))))
+ ("lux i64 *" +3 (:coerce Int (\ right hash value))))))))
(def: #export (product left right)
(All [l r] (-> (Hash l) (Hash r) (Hash (& l r))))
(structure
(def: &equivalence
- (equivalence.product (:: left &equivalence)
- (:: right &equivalence)))
+ (equivalence.product (\ left &equivalence)
+ (\ right &equivalence)))
(def: (hash [leftV rightV])
(:coerce Nat
("lux i64 +"
- (:coerce Int (:: left hash leftV))
- (:coerce Int (:: right hash rightV)))))))
+ (:coerce Int (\ left hash leftV))
+ (:coerce Int (\ right hash rightV)))))))
diff --git a/stdlib/source/lux/abstract/interval.lux b/stdlib/source/lux/abstract/interval.lux
index c429fa5c8..b1b026440 100644
--- a/stdlib/source/lux/abstract/interval.lux
+++ b/stdlib/source/lux/abstract/interval.lux
@@ -75,14 +75,14 @@
(def: #export (union left right)
(All [a] (-> (Interval a) (Interval a) (Interval a)))
(structure (def: &enum (get@ #&enum right))
- (def: bottom (order.min (:: right &order) (:: left bottom) (:: right bottom)))
- (def: top (order.max (:: right &order) (:: left top) (:: right top)))))
+ (def: bottom (order.min (\ right &order) (\ left bottom) (\ right bottom)))
+ (def: top (order.max (\ right &order) (\ left top) (\ right top)))))
(def: #export (intersection left right)
(All [a] (-> (Interval a) (Interval a) (Interval a)))
(structure (def: &enum (get@ #&enum right))
- (def: bottom (order.max (:: right &order) (:: left bottom) (:: right bottom)))
- (def: top (order.min (:: right &order) (:: left top) (:: right top)))))
+ (def: bottom (order.max (\ right &order) (\ left bottom) (\ right bottom)))
+ (def: top (order.min (\ right &order) (\ left top) (\ right top)))))
(def: #export (complement interval)
(All [a] (-> (Interval a) (Interval a)))
@@ -94,9 +94,9 @@
(def: #export (precedes? reference sample)
(All [a] (-> (Interval a) (Interval a) Bit))
(let [(^open ".") reference
- limit (:: reference bottom)]
- (and (< limit (:: sample bottom))
- (< limit (:: sample top)))))
+ limit (\ reference bottom)]
+ (and (< limit (\ sample bottom))
+ (< limit (\ sample top)))))
(def: #export (succeeds? reference sample)
(All [a] (-> (Interval a) (Interval a) Bit))
@@ -116,9 +116,9 @@
(def: #export (meets? reference sample)
(All [a] (-> (Interval a) (Interval a) Bit))
(let [(^open ",\.") reference
- limit (:: reference bottom)]
- (and (,\= limit (:: sample top))
- (order.<= ,\&order limit (:: sample bottom)))))
+ limit (\ reference bottom)]
+ (and (,\= limit (\ sample top))
+ (order.<= ,\&order limit (\ sample bottom)))))
(def: #export (touches? reference sample)
(All [a] (-> (Interval a) (Interval a) Bit))
@@ -129,11 +129,11 @@
[(def: #export (<name> reference sample)
(All [a] (-> (Interval a) (Interval a) Bit))
(let [(^open ",\.") reference]
- (and (,\= (:: reference <eq-side>)
- (:: sample <eq-side>))
+ (and (,\= (\ reference <eq-side>)
+ (\ sample <eq-side>))
(<ineq> ,\&order
- (:: reference <ineq-side>)
- (:: sample <ineq-side>)))))]
+ (\ reference <ineq-side>)
+ (\ sample <ineq-side>)))))]
[starts? ,\bottom order.<= ,\top]
[finishes? ,\top order.>= ,\bottom]
@@ -142,8 +142,8 @@
(structure: #export equivalence (All [a] (Equivalence (Interval a)))
(def: (= reference sample)
(let [(^open ",\.") reference]
- (and (,\= ,\bottom (:: sample bottom))
- (,\= ,\top (:: sample top))))))
+ (and (,\= ,\bottom (\ sample bottom))
+ (,\= ,\top (\ sample top))))))
(def: #export (nested? reference sample)
(All [a] (-> (Interval a) (Interval a) Bit))
@@ -151,8 +151,8 @@
(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))))
+ (and (order.>= ,\&order (\ reference bottom) (\ sample bottom))
+ (order.<= ,\&order (\ reference top) (\ sample top))))
(or (singleton? reference)
(and (inner? reference) (outer? sample)))
@@ -160,16 +160,16 @@
## (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)))))
+ (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]
- (and (not (:: ..equivalence = reference sample))
+ (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 052191e66..1d7c67401 100644
--- a/stdlib/source/lux/abstract/monad.lux
+++ b/stdlib/source/lux/abstract/monad.lux
@@ -110,8 +110,8 @@
(All [! a b]
(-> (Monad !) (-> a (! b))
(-> (! a) (! b))))
- (|>> (:: monad map f)
- (:: monad join)))
+ (|>> (\ monad map f)
+ (\ monad join)))
(def: #export (seq monad)
{#.doc "Run all the monadic values in the list and produce a list of the base values."}
@@ -175,7 +175,7 @@
(M a)))
(case xs
#.Nil
- (:: monad wrap init)
+ (\ monad wrap init)
(#.Cons x xs')
(do monad
diff --git a/stdlib/source/lux/abstract/monad/free.lux b/stdlib/source/lux/abstract/monad/free.lux
index 5194963b4..3eb01064d 100644
--- a/stdlib/source/lux/abstract/monad/free.lux
+++ b/stdlib/source/lux/abstract/monad/free.lux
@@ -19,7 +19,7 @@
(#Pure (f a))
(#Effect value)
- (#Effect (:: dsl map (map f) value)))))
+ (#Effect (\ dsl map (map f) value)))))
(structure: #export (apply dsl)
(All [F] (-> (Functor F) (Apply (Free F))))
@@ -32,14 +32,14 @@
(#Pure (f a))
[(#Pure f) (#Effect fa)]
- (#Effect (:: dsl map
- (:: (..functor dsl) map f)
- fa))
+ (#Effect (\ dsl map
+ (\ (..functor dsl) map f)
+ fa))
[(#Effect ff) _]
- (#Effect (:: dsl map
- (function (_ f) (apply f ea))
- ff))
+ (#Effect (\ dsl map
+ (function (_ f) (apply f ea))
+ ff))
)))
(structure: #export (monad dsl)
@@ -61,7 +61,7 @@
(#Effect fa))
(#Effect fefa)
- (#Effect (:: dsl map
- (:: (monad dsl) join)
- fefa))
+ (#Effect (\ dsl map
+ (\ (monad dsl) join)
+ fefa))
)))
diff --git a/stdlib/source/lux/abstract/monad/indexed.lux b/stdlib/source/lux/abstract/monad/indexed.lux
index 14bbf75f0..4e6f51942 100644
--- a/stdlib/source/lux/abstract/monad/indexed.lux
+++ b/stdlib/source/lux/abstract/monad/indexed.lux
@@ -45,11 +45,11 @@
(def: named-monad
(Parser [(Maybe Text) Code])
- (p.either (s.record (p.and (:: p.monad map (|>> #.Some)
- s.local-identifier)
+ (p.either (s.record (p.and (\ p.monad map (|>> #.Some)
+ s.local-identifier)
s.any))
- (:: p.monad map (|>> [#.None])
- s.any)))
+ (\ p.monad map (|>> [#.None])
+ s.any)))
(syntax: #export (do {[?name monad] ..named-monad}
{context (s.tuple (p.some context))}
diff --git a/stdlib/source/lux/abstract/monoid.lux b/stdlib/source/lux/abstract/monoid.lux
index 7f4254af3..c87cf8b40 100644
--- a/stdlib/source/lux/abstract/monoid.lux
+++ b/stdlib/source/lux/abstract/monoid.lux
@@ -13,8 +13,8 @@
(All [l r] (-> (Monoid l) (Monoid r) (Monoid [l r])))
(structure
(def: identity
- [(:: left identity) (:: right identity)])
+ [(\ left identity) (\ right identity)])
(def: (compose [lL rL] [lR rR])
- [(:: left compose lL lR)
- (:: right compose rL rR)])))
+ [(\ left compose lL lR)
+ (\ right compose rL rR)])))
diff --git a/stdlib/source/lux/abstract/order.lux b/stdlib/source/lux/abstract/order.lux
index dad99b8b4..21f5739d2 100644
--- a/stdlib/source/lux/abstract/order.lux
+++ b/stdlib/source/lux/abstract/order.lux
@@ -22,28 +22,28 @@
(def: #export (<= order parameter subject)
Comparison
- (or (:: order < parameter subject)
- (:: order = parameter subject)))
+ (or (\ order < parameter subject)
+ (\ order = parameter subject)))
(def: #export (> order parameter subject)
Comparison
- (:: order < subject parameter))
+ (\ order < subject parameter))
(def: #export (>= order parameter subject)
Comparison
- (or (:: order < subject parameter)
- (:: order = subject parameter)))
+ (or (\ order < subject parameter)
+ (\ order = subject parameter)))
(type: #export (Choice a)
(-> (Order a) a a a))
(def: #export (min order x y)
Choice
- (if (:: order < y x) x y))
+ (if (\ order < y x) x y))
(def: #export (max order x y)
Choice
- (if (:: order < y x) y x))
+ (if (\ order < y x) y x))
(structure: #export functor
(contravariant.Functor Order)
@@ -51,7 +51,7 @@
(def: (map f order)
(structure
(def: &equivalence
- (:: equivalence.functor map f (:: order &equivalence)))
+ (\ equivalence.functor map f (\ order &equivalence)))
(def: (< reference sample)
- (:: order < (f reference) (f sample))))))
+ (\ order < (f reference) (f sample))))))