aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/concurrency/semaphore.lux
blob: 774acf5fad227d6c69592e10cd232eaf6ee13810 (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
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
(.module:
  [lux #*
   [control [monad (#+ do)]]
   [concurrency
    [atom (#+ Atom)]
    [promise (#+ Promise)]]
   [io (#+ IO)]
   [type
    abstract
    [refinement]]])

(type: State
  {#open-positions Nat
   #waiting-list (List (Promise Any))})

(abstract: #export Semaphore
  {#.doc "A tool for controlling access to resources by multiple concurrent processes."}

  (Atom State)

  (def: #export (semaphore init-open-positions)
    (-> Nat Semaphore)
    (:abstraction (atom.atom {#open-positions init-open-positions
                              #waiting-list (list)})))

  (def: #export (wait semaphore)
    (Ex [k] (-> Semaphore (Promise Any)))
    (let [semaphore (:representation semaphore)]
      (io.run
       (loop [signal (: (Promise Any)
                        (promise.promise #.None))]
         (do io.Monad<IO>
           [state (atom.read semaphore)
            #let [[ready? state'] (: [Bit State]
                                     (case (get@ #open-positions state)
                                       +0 [false (update@ #waiting-list (|>> (#.Cons signal))
                                                          state)]
                                       _ [true (update@ #open-positions dec
                                                        state)]))]
            success? (atom.compare-and-swap state state' semaphore)
            _ (if ready?
                (promise.resolve [] signal)
                (wrap false))]
           (if success?
             (wrap signal)
             (recur signal)))))))

  (def: #export (signal semaphore)
    (Ex [k] (-> Semaphore (Promise Any)))
    (let [semaphore (:representation semaphore)]
      (promise.future
       (loop [_ []]
         (do io.Monad<IO>
           [state (atom.read semaphore)
            #let [[?signal state'] (: [(Maybe (Promise Any)) State]
                                      (case (get@ #waiting-list state)
                                        #.Nil
                                        [#.None (update@ #open-positions inc state)]
                                        
                                        (#.Cons head tail)
                                        [(#.Some head) (set@ #waiting-list tail state)]))]
            success? (atom.compare-and-swap state state' semaphore)]
           (if success?
             (do @
               [_ (case ?signal
                    #.None
                    (wrap true)

                    (#.Some signal)
                    (promise.resolve [] signal))]
               (wrap []))
             (recur [])))))))
  )

(abstract: #export Mutex
  {#.doc "A mutual-exclusion lock that can only be acquired by one process at a time."}

  Semaphore

  (def: #export (mutex _)
    (-> Any Mutex)
    (:abstraction (semaphore +1)))

  (def: (acquire mutex)
    (-> Mutex (Promise Any))
    (wait (:representation mutex)))

  (def: (release mutex)
    (-> Mutex (Promise Any))
    (signal (:representation mutex)))

  (def: #export (synchronize mutex procedure)
    (All [a] (-> Mutex (IO (Promise a)) (Promise a)))
    (do promise.Monad<Promise>
      [_ (acquire mutex)
       output (io.run procedure)
       _ (release mutex)]
      (wrap output)))
  )

(def: #export limit (refinement.refinement (n/> +0)))
(`` (type: #export Limit (~~ (refinement.type limit))))

(abstract: #export Barrier
  {#.doc "A barrier that blocks all processes from proceeding until a given number of processes are parked at the barrier."}

  {#limit Limit
   #count (Atom Nat)
   #start-turnstile Semaphore
   #end-turnstile Semaphore}

  (def: #export (barrier limit)
    (-> Limit Barrier)
    (:abstraction {#limit limit
                   #count (atom.atom +0)
                   #start-turnstile (semaphore +0)
                   #end-turnstile (semaphore +0)}))

  (def: (un-block times turnstile)
    (-> Nat Semaphore (Promise Any))
    (loop [step +0]
      (if (n/< times step)
        (do promise.Monad<Promise>
          [_ (signal turnstile)]
          (recur (inc step)))
        (:: promise.Monad<Promise> wrap []))))

  (do-template [<phase> <update> <goal> <turnstile>]
    [(def: (<phase> (^:representation barrier))
       (-> Barrier (Promise Any))
       (do promise.Monad<Promise>
         [#let [limit (refinement.un-refine (get@ #limit barrier))
                goal <goal>
                count (io.run (atom.update <update> (get@ #count barrier)))]
          _ (if (n/= goal count)
              (un-block limit (get@ <turnstile> barrier))
              (wrap []))]
         (wait (get@ <turnstile> barrier))))]

    [start inc limit #start-turnstile]
    [end   dec +0    #end-turnstile]
    )

  (def: #export (block barrier)
    (-> Barrier (Promise Any))
    (do promise.Monad<Promise>
      [_ (start barrier)]
      (end barrier)))
  )