aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/tool/compiler/phase/extension/statement.lux
blob: 37ff93b9cca9a9f8576b2d942318998cf63f015f (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
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
(.module:
  [lux #*
   [control
    [monad (#+ do)]
    pipe]
   [data
    [text
     format]
    [collection
     ["." list ("#/." functor)]
     ["." dictionary]]]
   ["." macro]
   [type (#+ :share :extract)
    ["." check]]]
  ["." //
   ["." bundle]
   ["/." //
    [analysis
     ["." module]
     ["." type]]
    ["." translation]
    ["." statement (#+ Operation Handler Bundle)]
    [//
     ["." analysis]
     ["." synthesis (#+ Synthesis)]]]])

## TODO: Inline "evaluate!'" into "evaluate!" ASAP
(def: (evaluate!' translate code//type codeS)
  (All [anchor expression statement]
    (-> (translation.Phase anchor expression statement)
        Type
        Synthesis
        (Operation anchor expression statement [Type expression Any])))
  (statement.lift-translation
   (translation.with-buffer
     (do ///.monad
       [codeT (translate codeS)
        count translation.next
        codeV (translation.evaluate! (format "evaluate" (%n count)) codeT)]
       (wrap [code//type codeT codeV])))))

(def: (evaluate! type codeC)
  (All [anchor expression statement]
    (-> Type Code (Operation anchor expression statement [Type expression Any])))
  (do ///.monad
    [state (//.lift ///.get-state)
     #let [analyse (get@ [#statement.analysis #statement.phase] state)
           synthesize (get@ [#statement.synthesis #statement.phase] state)
           translate (get@ [#statement.translation #statement.phase] state)]
     [_ code//type codeA] (statement.lift-analysis
                           (analysis.with-scope
                             (type.with-fresh-env
                               (type.with-type type
                                 (do @
                                   [codeA (analyse codeC)]
                                   (wrap [type codeA]))))))
     codeS (statement.lift-synthesis
            (synthesize codeA))]
    (evaluate!' translate code//type codeS)))

## TODO: Inline "definition'" into "definition" ASAP
(def: (definition' translate name code//type codeS)
  (All [anchor expression statement]
    (-> (translation.Phase anchor expression statement)
        Name
        Type
        Synthesis
        (Operation anchor expression statement [Type expression Text Any])))
  (statement.lift-translation
   (translation.with-buffer
     (do ///.monad
       [codeT (translate codeS)
        codeN+V (translation.define! name codeT)]
       (wrap [code//type codeT codeN+V])))))

(def: (definition name ?type codeC)
  (All [anchor expression statement]
    (-> Name (Maybe Type) Code
        (Operation anchor expression statement [Type expression Text Any])))
  (do ///.monad
    [state (//.lift ///.get-state)
     #let [analyse (get@ [#statement.analysis #statement.phase] state)
           synthesize (get@ [#statement.synthesis #statement.phase] state)
           translate (get@ [#statement.translation #statement.phase] state)]
     [_ code//type codeA] (statement.lift-analysis
                           (analysis.with-scope
                             (type.with-fresh-env
                               (case ?type
                                 (#.Some type)
                                 (type.with-type type
                                   (do @
                                     [codeA (analyse codeC)]
                                     (wrap [type codeA])))

                                 #.None
                                 (do @
                                   [[code//type codeA] (type.with-inference (analyse codeC))
                                    code//type (type.with-env
                                                 (check.clean code//type))]
                                   (wrap [code//type codeA]))))))
     codeS (statement.lift-synthesis
            (synthesize codeA))]
    (definition' translate name code//type codeS)))

(def: (define short-name type annotations value)
  (All [anchor expression statement]
    (-> Text Type Code Any
        (Operation anchor expression statement Any)))
  (statement.lift-analysis
   (do ///.monad
     [_ (module.define short-name [type annotations value])]
     (if (macro.type? annotations)
       (case (macro.declared-tags annotations)
         #.Nil
         (wrap [])

         tags
         (module.declare-tags tags (macro.export? annotations) (:coerce Type value)))
       (wrap [])))))

(def: lux::def
  Handler
  (function (_ extension-name phase inputsC+)
    (case inputsC+
      (^ (list [_ (#.Identifier ["" short-name])] valueC annotationsC))
      (do ///.monad
        [current-module (statement.lift-analysis
                         (//.lift macro.current-module-name))
         #let [full-name [current-module short-name]]
         [_ annotationsT annotationsV] (evaluate! Code annotationsC)
         #let [annotationsV (:coerce Code annotationsV)]
         [value//type valueT valueN valueV] (..definition full-name
                                                          (if (macro.type? annotationsV)
                                                            (#.Some Type)
                                                            #.None)
                                                          valueC)
         _ (..define short-name value//type annotationsV valueV)
         #let [_ (log! (format "Definition " (%name full-name)))]]
        (statement.lift-translation
         (translation.learn full-name valueN)))

      _
      (///.throw //.invalid-syntax [extension-name]))))

(def: (alias! alias def-name)
  (-> Text Name (analysis.Operation Any))
  (do ///.monad
    [definition (//.lift (macro.find-def def-name))]
    (module.define alias definition)))

(def: def::module
  Handler
  (function (_ extension-name phase inputsC+)
    (case inputsC+
      (^ (list annotationsC))
      (do ///.monad
        [[_ annotationsT annotationsV] (evaluate! Code annotationsC)
         _ (statement.lift-analysis
            (module.set-annotations (:coerce Code annotationsV)))]
        (wrap []))

      _
      (///.throw //.invalid-syntax [extension-name]))))

(def: def::alias
  Handler
  (function (_ extension-name phase inputsC+)
    (case inputsC+
      (^ (list [_ (#.Identifier ["" alias])] [_ (#.Identifier def-name)]))
      (//.lift
       (///.sub [(get@ [#statement.analysis #statement.state])
                 (set@ [#statement.analysis #statement.state])]
                (alias! alias def-name)))

      _
      (///.throw //.invalid-syntax [extension-name]))))

(do-template [<mame> <type> <scope>]
  [(def: <mame>
     (All [anchor expression statement]
       (Handler anchor expression statement))
     (function (handler extension-name phase inputsC+)
       (case inputsC+
         (^ (list [_ (#.Text name)] valueC))
         (do ///.monad
           [[_ handlerT handlerV] (evaluate! (:extract [anchor expression statement]
                                                       {(Handler anchor expression statement)
                                                        handler}
                                                       <type>)
                                             valueC)]
           (<| <scope>
               (//.install name)
               (:share [anchor expression statement]
                       {(Handler anchor expression statement)
                        handler}
                       {<type>
                        (:assume handlerV)})))

         _
         (///.throw //.invalid-syntax [extension-name]))))]

  [def::analysis    analysis.Handler                                  statement.lift-analysis]
  [def::synthesis   synthesis.Handler                                 statement.lift-synthesis]
  [def::translation (translation.Handler anchor expression statement) statement.lift-translation]
  [def::statement   (statement.Handler anchor expression statement)   (<|)]
  )

(def: bundle::def
  Bundle
  (<| (bundle.prefix "def")
      (|> bundle.empty
          (dictionary.put "module"      def::module)
          (dictionary.put "alias"       def::alias)
          (dictionary.put "analysis"    def::analysis)
          (dictionary.put "synthesis"   def::synthesis)
          (dictionary.put "translation" def::translation)
          (dictionary.put "statement"   def::statement)
          )))

(def: #export bundle
  Bundle
  (<| (bundle.prefix "lux")
      (|> bundle.empty
          (dictionary.put "def" lux::def)
          (dictionary.merge ..bundle::def))))