aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/abstract/interval.lux
diff options
context:
space:
mode:
Diffstat (limited to '')
-rw-r--r--stdlib/source/lux/abstract/interval.lux50
1 files changed, 25 insertions, 25 deletions
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)