diff options
Diffstat (limited to '')
-rw-r--r-- | stdlib/source/lux/control/cont.lux | 30 |
1 files changed, 15 insertions, 15 deletions
diff --git a/stdlib/source/lux/control/cont.lux b/stdlib/source/lux/control/cont.lux index c3be37b73..35f549ee7 100644 --- a/stdlib/source/lux/control/cont.lux +++ b/stdlib/source/lux/control/cont.lux @@ -24,25 +24,25 @@ (struct: #export Functor<Cont> (All [o] (Functor (All [i] (Cont i o)))) (def: (map f fv) - (function [k] (fv (compose k f))))) + (function (_ k) (fv (compose k f))))) (struct: #export Applicative<Cont> (All [o] (Applicative (All [i] (Cont i o)))) (def: functor Functor<Cont>) (def: (wrap value) - (function [k] (k value))) + (function (_ k) (k value))) (def: (apply ff fv) - (function [k] + (function (_ k) (|> (k (f v)) - (function [v]) fv - (function [f]) ff)))) + (function (_ v)) fv + (function (_ f)) ff)))) (struct: #export Monad<Cont> (All [o] (Monad (All [i] (Cont i o)))) (def: applicative Applicative<Cont>) (def: (join ffa) - (function [k] + (function (_ k) (ffa (continue k))))) (def: #export (call/cc f) @@ -51,15 +51,15 @@ (-> (-> (-> a (Cont b z)) (Cont a z)) (Cont a z))) - (function [k] - (f (function [a] (function [_] (k a))) + (function (_ k) + (f (function (_ a) (function (_ _) (k a))) k))) (syntax: #export (pending expr) {#.doc (doc "Turns any expression into a function that is pending a continuation." (pending (some-function some-input)))} - (with-gensyms [g!k] - (wrap (list (` (.function [(~ g!k)] ((~ g!k) (~ expr)))))))) + (with-gensyms [g!_ g!k] + (wrap (list (` (.function ((~ g!_) (~ g!k)) ((~ g!k) (~ expr)))))))) (def: #export (portal init) (All [i o z] @@ -67,16 +67,16 @@ (Cont [(-> i (Cont o z)) i] z))) - (call/cc (function [k] + (call/cc (function (_ k) (do Monad<Cont> - [#let [nexus (function nexus [val] + [#let [nexus (function (nexus val) (k [nexus val]))] _ (k [nexus init])] (wrap (undefined)))))) (def: #export (reset scope) (All [i o] (-> (Cont i i) (Cont i o))) - (function [k] + (function (_ k) (k (run scope)))) (def: #export (shift f) @@ -84,6 +84,6 @@ (-> (-> (-> a (Cont a a)) (Cont a a)) (Cont a a))) - (function [oc] - (f (function [a] (function [ic] (ic (oc a)))) + (function (_ oc) + (f (function (_ a) (function (_ ic) (ic (oc a)))) id))) |