aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/meta/compiler/meta/archive.lux
blob: 46ede92f0331f0ad3249e2075ee59f409282f786 (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
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
(.require
 [library
  [lux (.except Module #module has)
   [abstract
    ["[0]" equivalence (.only Equivalence)]
    ["[0]" monad (.only do)]]
   [control
    ["<>" parser]
    ["[0]" maybe]
    ["[0]" try (.only Try)]
    ["[0]" exception (.only Exception)]
    ["[0]" function]]
   [data
    ["[0]" product]
    ["[0]" binary (.only Binary)
     ["[0]" \\format (.only Format)]
     ["<[1]>" \\parser (.only Parser)]]
    ["[0]" text (.only)
     ["%" \\format]]
    [collection
     ["[0]" list (.use "[1]#[0]" functor mix)]
     ["[0]" dictionary (.only Dictionary)]
     ["[0]" set]
     ["[0]" sequence (.only Sequence)]]]
   [math
    [number
     ["n" nat (.use "[1]#[0]" equivalence)]]]
   [meta
    ["[0]" configuration (.only Configuration)]
    [type
     [primitive (.except)]]]]]
 [/
  ["[0]" artifact]
  ["[0]" registry (.only Registry)]
  ["[0]" signature (.only Signature)]
  ["[0]" key (.only Key)]
  ["[0]" module (.only Module)
   ["[0]" descriptor (.only Descriptor)]
   ["[0]" document (.only Document)]]
  [///
   [version (.only Version)]]])

(type .public Output
  (Sequence [artifact.ID (Maybe Text) Binary]))

(exception.def .public (unknown_document [module known_modules])
  (Exception [descriptor.Module (List descriptor.Module)])
  (exception.report
   (list ["Module" (%.text module)]
         ["Known Modules" (exception.listing %.text known_modules)])))

(exception.def .public (cannot_replace_document [module old new])
  (Exception [descriptor.Module (Document Any) (Document Any)])
  (exception.report
   (list ["Module" (%.text module)]
         ["Old key" (signature.description (document.signature old))]
         ["New key" (signature.description (document.signature new))])))

(with_template [<name>]
  [(exception.def .public (<name> it)
     (Exception descriptor.Module)
     (exception.report
      (list ["Module" (%.text it)])))]

  [module_has_already_been_reserved]
  [module_must_be_reserved_before_it_can_be_added]
  [module_is_only_reserved]
  )

(type .public (Entry a)
  (Record
   [#module (Module a)
    #output Output
    #registry Registry]))

(primitive .public Archive
  (Record
   [#next module.ID
    #resolver (Dictionary descriptor.Module [module.ID (Maybe (Entry Any))])])

  (def next
    (-> Archive module.ID)
    (|>> representation (the #next)))

  (def .public empty
    Archive
    (abstraction [#next 0
                  #resolver (dictionary.empty text.hash)]))

  (def .public (id module archive)
    (-> descriptor.Module Archive (Try module.ID))
    (let [(open "/[0]") (representation archive)]
      (when (dictionary.value module /#resolver)
        {.#Some [id _]}
        {try.#Success id}
        
        {.#None}
        (exception.except ..unknown_document [module
                                              (dictionary.keys /#resolver)]))))

  (def .public (reserve module archive)
    (-> descriptor.Module Archive (Try [module.ID Archive]))
    (let [(open "/[0]") (representation archive)]
      (when (dictionary.value module /#resolver)
        {.#Some _}
        (exception.except ..module_has_already_been_reserved [module])
        
        {.#None}
        {try.#Success [/#next
                       (|> archive
                           representation
                           (revised #resolver (dictionary.has module [/#next (is (Maybe (Entry Any)) {.#None})]))
                           (revised #next ++)
                           abstraction)]})))

  (def .public (has module entry archive)
    (-> descriptor.Module (Entry Any) Archive (Try Archive))
    (let [(open "/[0]") (representation archive)]
      (when (dictionary.value module /#resolver)
        {.#Some [id {.#None}]}
        {try.#Success (|> archive
                          representation
                          (revised ..#resolver (dictionary.has module [id {.#Some entry}]))
                          abstraction)}
        
        {.#Some [id {.#Some [existing_module existing_output existing_registry]}]}
        (if (same? (the module.#document existing_module)
                   (the [#module module.#document] entry))
          ... TODO: Find out why this code allows for the same module to be added more than once. It looks fishy...
          {try.#Success archive}
          (exception.except ..cannot_replace_document [module (the module.#document existing_module) (the [#module module.#document] entry)]))
        
        {.#None}
        (exception.except ..module_must_be_reserved_before_it_can_be_added [module]))))

  (def .public entries
    (-> Archive (List [descriptor.Module [module.ID (Entry Any)]]))
    (|>> representation
         (the #resolver)
         dictionary.entries
         (list.all (function (_ [module [module_id entry]])
                     (at maybe.monad each (|>> [module_id] [module]) entry)))))

  (def .public (find module archive)
    (-> descriptor.Module Archive (Try (Entry Any)))
    (let [(open "/[0]") (representation archive)]
      (when (dictionary.value module /#resolver)
        {.#Some [id {.#Some entry}]}
        {try.#Success entry}

        {.#Some [id {.#None}]}
        (exception.except ..module_is_only_reserved [module])
        
        {.#None}
        (exception.except ..unknown_document [module (dictionary.keys /#resolver)]))))

  (def .public (archived? archive module)
    (-> Archive descriptor.Module Bit)
    (when (..find module archive)
      {try.#Success _}
      true

      {try.#Failure _}
      false))

  (def .public archived
    (-> Archive (List descriptor.Module))
    (|>> representation
         (the #resolver)
         dictionary.entries
         (list.all (function (_ [module [id descriptor+document]])
                     (when descriptor+document
                       {.#Some _} {.#Some module}
                       {.#None} {.#None})))))

  (def .public (reserved? archive module)
    (-> Archive descriptor.Module Bit)
    (let [(open "/[0]") (representation archive)]
      (when (dictionary.value module /#resolver)
        {.#Some [id _]}
        true

        {.#None}
        false)))

  (def .public reserved
    (-> Archive (List descriptor.Module))
    (|>> representation
         (the #resolver)
         dictionary.keys))

  (def .public reservations
    (-> Archive (List [descriptor.Module module.ID]))
    (|>> representation
         (the #resolver)
         dictionary.entries
         (list#each (function (_ [module [id _]])
                      [module id]))))

  (def .public (composite additions archive)
    (-> Archive Archive Archive)
    (let [[+next +resolver] (representation additions)]
      (|> archive
          representation
          (revised #next (n.max +next))
          (revised #resolver (function (_ resolver)
                               (list#mix (function (_ [module [id entry]] resolver)
                                           (when entry
                                             {.#Some _}
                                             (dictionary.has module [id entry] resolver)
                                             
                                             {.#None}
                                             resolver))
                                         resolver
                                         (dictionary.entries +resolver))))
          abstraction)))

  (type Reservation
    [descriptor.Module module.ID])

  (type Frozen
    [Version Configuration module.ID (List Reservation)])
  
  (def parser
    (Parser ..Frozen)
    (all <>.and
         <binary>.nat
         (<binary>.list (<>.and <binary>.text <binary>.text))
         <binary>.nat
         (<binary>.list (<>.and <binary>.text <binary>.nat))))

  (def format
    (Format ..Frozen)
    (all \\format.and
         \\format.nat
         (\\format.list (\\format.and \\format.text \\format.text))
         \\format.nat
         (\\format.list (\\format.and \\format.text \\format.nat))))
  
  (def .public (export version configuration archive)
    (-> Version Configuration Archive Binary)
    (let [(open "/[0]") (representation archive)]
      (|> /#resolver
          dictionary.entries
          (list.all (function (_ [module [id descriptor+document]])
                      (when descriptor+document
                        {.#Some _} {.#Some [module id]}
                        {.#None} {.#None})))
          [version configuration /#next]
          (\\format.result ..format))))

  (exception.def .public (version_mismatch [expected actual])
    (Exception [Version Version])
    (exception.report
     (list ["Expected" (%.nat expected)]
           ["Actual" (%.nat actual)])))

  (exception.def .public (configuration_mismatch [expected actual])
    (Exception [Configuration Configuration])
    (exception.report
     (list ["Expected" (configuration.format expected)]
           ["Actual" (configuration.format actual)])))

  (def .public (import expected_version expected_configuration binary)
    (-> Version Configuration Binary (Try Archive))
    (do try.monad
      [[actual_version actual_configuration next reservations] (<binary>.result ..parser binary)
       _ (exception.assertion ..version_mismatch [expected_version actual_version]
                              (n#= expected_version actual_version))
       _ (exception.assertion ..configuration_mismatch [expected_configuration actual_configuration]
                              (at configuration.equivalence =
                                  expected_configuration
                                  actual_configuration))]
      (in (abstraction
           [#next next
            #resolver (list#mix (function (_ [module id] archive)
                                  (dictionary.has module [id (is (Maybe (Entry Any)) {.#None})] archive))
                                (the #resolver (representation ..empty))
                                reservations)]))))
  )