aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/control/concurrency/frp.lux
diff options
context:
space:
mode:
Diffstat (limited to 'stdlib/source/library/lux/control/concurrency/frp.lux')
-rw-r--r--stdlib/source/library/lux/control/concurrency/frp.lux94
1 files changed, 47 insertions, 47 deletions
diff --git a/stdlib/source/library/lux/control/concurrency/frp.lux b/stdlib/source/library/lux/control/concurrency/frp.lux
index 5498eeb06..ebf3728ca 100644
--- a/stdlib/source/library/lux/control/concurrency/frp.lux
+++ b/stdlib/source/library/lux/control/concurrency/frp.lux
@@ -39,10 +39,10 @@
(loop [_ []]
(do [! io.monad]
[current (atom.read! sink)
- stopped? (current #.None)]
+ stopped? (current {.#None})]
(if stopped?
... I closed the sink.
- (in {#try.Success []})
+ (in {try.#Success []})
... Someone else interacted with the sink.
(do !
[latter (atom.read! sink)]
@@ -63,12 +63,12 @@
[(Async (Maybe [a (Channel a)]))
(async.Resolver (Maybe [a (Channel a)]))]
(async.async []))]
- fed? (current {#.Some [value next]})]
+ fed? (current {.#Some [value next]})]
(if fed?
... I fed the sink.
(do !
[_ (atom.compare_and_swap! current resolve_next sink)]
- (in {#try.Success []}))
+ (in {try.#Success []}))
... Someone else interacted with the sink.
(do !
[latter (atom.read! sink)]
@@ -102,15 +102,15 @@
[item_f ff
item_a fa]
(case [item_f item_a]
- [{#.Some [head_f tail_f]} {#.Some [head_a tail_a]}]
- (in {#.Some [(head_f head_a) (on tail_a tail_f)]})
+ [{.#Some [head_f tail_f]} {.#Some [head_a tail_a]}]
+ (in {.#Some [(head_f head_a) (on tail_a tail_f)]})
_
- (in #.None)))))
+ (in {.#None})))))
(def: empty
Channel
- (async.resolved #.None))
+ (async.resolved {.#None}))
(implementation: .public monad
(Monad Channel)
@@ -118,7 +118,7 @@
(def: &functor ..functor)
(def: (in a)
- (async.resolved {#.Some [a ..empty]}))
+ (async.resolved {.#Some [a ..empty]}))
(def: (conjoint mma)
(let [[output sink] (channel [])]
@@ -128,22 +128,22 @@
(do [! async.monad]
[?mma mma]
(case ?mma
- {#.Some [ma mma']}
+ {.#Some [ma mma']}
(do !
[_ (loop [ma ma]
(do !
[?ma ma]
(case ?ma
- {#.Some [a ma']}
+ {.#Some [a ma']}
(exec
(io.run! (\ sink feed a))
(recur ma'))
- #.None
+ {.#None}
(in []))))]
(recur mma'))
- #.None
+ {.#None}
(in (: Any (io.run! (\ sink close))))))))
output))))
@@ -158,15 +158,15 @@
(do async.monad
[item channel]
(case item
- {#.Some [head tail]}
+ {.#Some [head tail]}
(case (io.run! (subscriber head))
- {#.Some _}
+ {.#Some _}
(recur tail)
- #.None
+ {.#None}
(in []))
- #.None
+ {.#None}
(in [])))))
[])))
@@ -175,19 +175,19 @@
(do async.monad
[item channel]
(case item
- {#.Some [head tail]}
+ {.#Some [head tail]}
(let [tail' (only pass? tail)]
(if (pass? head)
- (in {#.Some [head tail']})
+ (in {.#Some [head tail']})
tail'))
- #.None
- (in #.None))))
+ {.#None}
+ (in {.#None}))))
(def: .public (of_async async)
(All (_ a) (-> (Async a) (Channel a)))
(async\each (function (_ value)
- {#.Some [value ..empty]})
+ {.#Some [value ..empty]})
async))
(def: .public (mix f init channel)
@@ -197,10 +197,10 @@
(do [! async.monad]
[item channel]
(case item
- #.None
+ {.#None}
(in init)
- {#.Some [head tail]}
+ {.#Some [head tail]}
(do !
[init' (f head init)]
(mix f init' tail)))))
@@ -212,13 +212,13 @@
(do [! async.monad]
[item channel]
(case item
- #.None
- (in {#.Some [init (in #.None)]})
+ {.#None}
+ (in {.#Some [init (in {.#None})]})
- {#.Some [head tail]}
+ {.#Some [head tail]}
(do !
[init' (f head init)]
- (in {#.Some [init (mixes f init' tail)]})))))
+ (in {.#Some [init (mixes f init' tail)]})))))
(def: .public (poll milli_seconds action)
(All (_ a)
@@ -241,55 +241,55 @@
(do async.monad
[?next (f init)]
(case ?next
- {#.Some [state output]}
- (in {#.Some [output (iterations f state)]})
+ {.#Some [state output]}
+ (in {.#Some [output (iterations f state)]})
- #.None
- (in #.None))))
+ {.#None}
+ (in {.#None}))))
(def: (distinct' equivalence previous channel)
(All (_ a) (-> (Equivalence a) a (Channel a) (Channel a)))
(do async.monad
[item channel]
(case item
- {#.Some [head tail]}
+ {.#Some [head tail]}
(if (\ equivalence = previous head)
(distinct' equivalence previous tail)
- (in {#.Some [head (distinct' equivalence head tail)]}))
+ (in {.#Some [head (distinct' equivalence head tail)]}))
- #.None
- (in #.None))))
+ {.#None}
+ (in {.#None}))))
(def: .public (distinct equivalence channel)
(All (_ a) (-> (Equivalence a) (Channel a) (Channel a)))
(do async.monad
[item channel]
(in (case item
- {#.Some [head tail]}
- {#.Some [head (distinct' equivalence head tail)]}
+ {.#Some [head tail]}
+ {.#Some [head (distinct' equivalence head tail)]}
- #.None
- #.None))))
+ {.#None}
+ {.#None}))))
(def: .public (list channel)
(All (_ a) (-> (Channel a) (Async (List a))))
(do [! async.monad]
[item channel]
(case item
- {#.Some [head tail]}
- (\ ! each (|>> {#.Item head})
+ {.#Some [head tail]}
+ (\ ! each (|>> {.#Item head})
(list tail))
- #.None
- (in #.End))))
+ {.#None}
+ (in {.#End}))))
(def: .public (sequential milli_seconds values)
(All (_ a) (-> Nat (List a) (Channel a)))
(case values
- #.End
+ {.#End}
..empty
- {#.Item head tail}
- (async.resolved {#.Some [head (do async.monad
+ {.#Item head tail}
+ (async.resolved {.#Some [head (do async.monad
[_ (async.delay milli_seconds)]
(sequential milli_seconds tail))]})))