aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/io.lux
blob: 726191aea423115537a9fe95593819ffe07639c3 (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
(.module: {#.doc "A method for abstracting I/O and effectful computations to make it safe while writing pure functional code."}
  lux
  (lux (control [functor #+ Functor]
                [apply #+ Apply]
                [monad #+ do Monad]
                ["ex" exception #+ Exception])
       (data ["e" error #+ Error]
             (coll [list]))))

(type: #export (IO a)
  {#.doc "A type that represents synchronous, effectful computations that may interact with the outside world."}
  (-> Nothing a))

(macro: #export (io tokens state)
  {#.doc (doc "Delays the evaluation of an expression, by wrapping it in an IO 'thunk'."
              "Great for wrapping effectful computations (which will not be performed until the IO is \"run\")."
              (io (exec
                    (log! msg)
                    "Some value...")))}
  (case tokens
    (^ (list value))
    (let [blank (: Code [["" +0 +0] (#.Symbol ["" ""])])]
      (#.Right [state (list (` ([(~ blank) (~ blank)] (~ value))))]))

    _
    (#.Left "Wrong syntax for io")))

(struct: #export _ (Functor IO)
  (def: (map f ma)
    (io (f (ma (:coerce Nothing []))))))

(struct: #export _ (Apply IO)
  (def: functor Functor<IO>)

  (def: (apply ff fa)
    (io ((ff (:coerce Nothing [])) (fa (:coerce Nothing []))))))

(struct: #export _ (Monad IO)
  (def: functor Functor<IO>)

  (def: (wrap x)
    (io x))
  
  (def: (join mma)
    (io ((mma (:coerce Nothing [])) (:coerce Nothing [])))))

(def: #export (run action)
  {#.doc "A way to execute IO computations and perform their side-effects."}
  (All [a] (-> (IO a) a))
  (action (:coerce Nothing [])))

(def: #export (exit code)
  (-> Int (IO Nothing))
  (io ("lux io exit" code)))

## Process
(type: #export (Process a)
  (IO (Error a)))

(struct: #export _ (Functor Process)
  (def: (map f ma)
    (io (:: e.Functor<Error> map f (run ma)))))

(struct: #export _ (Apply Process)
  (def: functor Functor<Process>)

  (def: (apply ff fa)
    (io (:: e.Apply<Error> apply (run ff) (run fa)))))

(struct: #export _ (Monad Process)
  (def: functor Functor<Process>)

  (def: (wrap x)
    (io (:: e.Monad<Error> wrap x)))
  
  (def: (join mma)
    (case (run mma)
      (#e.Success ma)
      ma
      
      (#e.Error error)
      (io (#e.Error error)))))

(def: #export (fail error)
  (All [a] (-> Text (Process a)))
  (io (#e.Error error)))

(def: #export (throw exception message)
  (All [e a] (-> (Exception e) e (Process a)))
  (io (ex.throw exception message)))