aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/control/continuation.lux
blob: 5bfe690e325a68d3c7b6bcbef1f699f3f69c9842 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
(.module:
  [lux #*
   [abstract
    [functor (#+ Functor)]
    [apply (#+ Apply)]
    [monad (#+ Monad do)]]
   [control
    ["." function]
    [parser
     ["s" code]]]
   [macro (#+ with-gensyms)
    ["." code]
    [syntax (#+ syntax:)]]])

(type: #export (Cont i o)
  {#.doc "Continuations."}
  (-> (-> i o) o))

(def: #export (continue next cont)
  {#.doc "Continues a continuation thunk."}
  (All [i o] (-> (-> i o) (Cont i o) o))
  (cont next))

(def: #export (run cont)
  {#.doc "Forces a continuation thunk to be evaluated."}
  (All [a] (-> (Cont a a) a))
  (cont function.identity))

(def: #export (call/cc f)
  {#.doc "Call with current continuation."}
  (All [a b z]
    (-> (-> (-> a (Cont b z))
            (Cont a z))
        (Cont a z)))
  (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!_ g!k]
    (wrap (list (` (.function ((~ g!_) (~ g!k)) ((~ g!k) (~ expr))))))))

(def: #export (reset scope)
  (All [i o] (-> (Cont i i) (Cont i o)))
  (function (_ k)
    (k (run scope))))

(def: #export (shift f)
  (All [a]
    (-> (-> (-> a (Cont a a))
            (Cont a a))
        (Cont a a)))
  (function (_ oc)
    (f (function (_ a) (function (_ ic) (ic (oc a))))
       function.identity)))

(structure: #export functor (All [o] (Functor (All [i] (Cont i o))))
  (def: (map f fv)
    (function (_ k) (fv (function.compose k f)))))

(structure: #export apply (All [o] (Apply (All [i] (Cont i o))))
  (def: &functor ..functor)

  (def: (apply ff fv)
    (function (_ k)
      (|> (k (f v))
          (function (_ v)) fv
          (function (_ f)) ff))))

(structure: #export monad (All [o] (Monad (All [i] (Cont i o))))
  (def: &functor ..functor)

  (def: (wrap value)
    (function (_ k) (k value)))

  (def: (join ffa)
    (function (_ k)
      (ffa (continue k)))))

(def: #export (portal init)
  (All [i o z]
    (-> i
        (Cont [(-> i (Cont o z))
               i]
              z)))
  (call/cc (function (_ k)
             (do ..monad
               [#let [nexus (function (nexus val)
                              (k [nexus val]))]
                _ (k [nexus init])]
               (wrap (undefined))))))