aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/program/compositor.lux
blob: ac17513ed29fd540a3c938f7074cb3cc56e2fe90 (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
(.require
 [library
  [lux (.except Module)
   ["[0]" debug]
   [abstract
    ["[0]" monad (.only do)]]
   [control
    ["[0]" io (.only IO io)]
    ["[0]" maybe]
    ["[0]" try (.only Try)]
    [concurrency
     ["[0]" async (.only Async) (.use "[1]#[0]" monad)]]]
   [data
    [binary (.only Binary)]
    ["[0]" product]
    ["[0]" text (.only)
     ["%" \\format (.only format)]]
    [collection
     ["[0]" dictionary (.only Dictionary)]]]
   [meta
    [type (.only sharing)]
    ["@" target]
    ["[0]" compiler
     ["[0]" phase]
     [default
      ["[0]" platform (.only Platform)]]
     [language
      ["$" lux (.only)
       ["[1]/[0]" program (.only Program)]
       ["[0]" syntax]
       ["[0]" generation]
       ["[0]" declaration]
       ["[0]" analysis (.only)
        [macro (.only Expander)]]
       [phase
        [extension (.only Extender)]]]]
     [meta
      [packager (.only Packager)]
      [context (.only Context)]
      ["[0]" cli (.only Service)]
      ["[0]" import]
      ["[0]" export]
      ["[0]" cache
       ["[1]" archive]]
      [archive (.only Archive)
       ["[0]" unit]
       [module
        [descriptor (.only Module)]]]
      [io
       ["ioW" archive]]]]
    ... ["[0]" interpreter]
    ]
   [time
    ["[0]" instant]]
   ["[0]" world
    ["[0]" file]
    ["[0]" console]
    ["[1]/[0]" environment]]]])

(def (or_crash! failure_description action)
  (All (_ a)
    (-> Text (Async (Try a)) (Async a)))
  (do [! async.monad]
    [?output action]
    (case ?output
      {try.#Failure error}
      (let [report (format text.new_line
                           failure_description text.new_line
                           error text.new_line)]
        (do !
          [_ (with_expansions [<else> (in {try.#Success (debug.log! report)})]
               (for @.js (is (Async (Try Any))
                             (case console.default
                               {.#None}
                               <else>

                               {.#Some console}
                               (console.write_line report console)))
                    (is (Async (Try Any))
                        <else>)))]
          (io.run! (at world/environment.default exit +1))))

      {try.#Success output}
      (in output))))

(def (timed process)
  (All (_ a)
    (-> (Async (Try a)) (Async (Try a))))
  (do async.monad
    [.let [start (io.run! instant.now)]
     output process
     .let [_ ("lux io log" (|> (io.run! instant.now)
                               (instant.span start)
                               %.duration
                               (format "Duration: ")))]]
    (in output)))

(def (package! fs host_dependencies [packager package] archive context)
  (-> (file.System Async) (Dictionary file.Path Binary) [Packager file.Path] Archive (Maybe unit.ID) (Async (Try Any)))
  (case (packager host_dependencies archive context)
    {try.#Success content}
    (case content
      {.#Left content}
      (at fs write package content)
      
      {.#Right content}
      (do [! (try.with async.monad)]
        [_ (at fs make_directory package)
         _ (monad.each ! (function (_ [name content])
                           (at fs write (file.rooted fs package name) content))
                       content)]
        (in [])))
    
    {try.#Failure error}
    (at async.monad in {try.#Failure error})))

(def (load_host_dependencies fs host_dependencies)
  (-> (file.System Async) (List file.Path) (Async (Try (Dictionary file.Path Binary))))
  (do [! (try.with async.monad)]
    []
    (loop (again [pending host_dependencies
                  output (is (Dictionary file.Path Binary)
                             (dictionary.empty text.hash))])
      (case pending
        {.#End}
        (in output)

        {.#Item head tail}
        (do !
          [content (at fs read head)]
          (again tail
                 (dictionary.has head content output)))))))

(with_expansions [<parameters> (these anchor expression artifact)]
  (def .public (compiler lux_compiler file_context
                         expander host_analysis platform generation_bundle host_declaration_bundle program anchorT,expressionT,declarationT extender
                         service
                         packager,package)
    (All (_ <parameters>)
      (-> (-> Any platform.Custom)
          Context
          Expander
          analysis.Bundle
          (IO (Platform <parameters>))
          (generation.Bundle <parameters>)
          (-> phase.Wrapper (declaration.Bundle <parameters>))
          (Program expression artifact)
          [Type Type Type]
          (-> phase.Wrapper Extender)
          Service
          [Packager file.Path]
          (Async Any)))
    (do [! async.monad]
      [platform (async.future platform)]
      (case service
        {cli.#Compilation compilation}
        (<| (or_crash! "Compilation failed:")
            ..timed
            (do (try.with async.monad)
              [.let [[compilation_host_dependencies compilation_libraries compilation_compilers compilation_sources compilation_target compilation_module compilation_configuration] compilation]
               import (import.import (the platform.#file_system platform) compilation_libraries)
               [state archive phase_wrapper] (sharing [<parameters>]
                                               (is (Platform <parameters>)
                                                   platform)
                                               (is (Async (Try [(declaration.State+ <parameters>)
                                                                Archive
                                                                phase.Wrapper]))
                                                   (as_expected (platform.initialize file_context compilation_module expander host_analysis platform generation_bundle host_declaration_bundle program anchorT,expressionT,declarationT extender
                                                                                     import compilation_sources compilation_configuration))))
               [archive state] (sharing [<parameters>]
                                 (is (Platform <parameters>)
                                     platform)
                                 (is (Async (Try [Archive (declaration.State+ <parameters>)]))
                                     (as_expected (platform.compile lux_compiler phase_wrapper import file_context expander platform compilation [archive state]))))
               _ (cache.cache! (the platform.#file_system platform) file_context archive)
               host_dependencies (..load_host_dependencies (the platform.#file_system platform) compilation_host_dependencies)
               _ (..package! (for @.old (file.async file.default)
                                  @.jvm (file.async file.default)
                                  ... TODO: Handle this in a safer manner.
                                  ... This would crash if the compiler was run on a browser.
                                  @.js (maybe.trusted file.default))
                             host_dependencies
                             packager,package
                             archive
                             (try.maybe ($/program.context archive)))]
              (in (debug.log! "Compilation complete!"))))

        {cli.#Export export}
        (<| (or_crash! "Export failed:")
            (do (try.with async.monad)
              [_ (export.export (the platform.#file_system platform)
                   export)]
              (in (debug.log! "Export complete!"))))
        
        {cli.#Interpretation interpretation}
        ... TODO: Fix the interpreter...
        (undefined)
        ... (<| (or_crash! "Interpretation failed:")
        ...     (do [! async.monad]
        ...       [console (|> console.default
        ...                    async.future
        ...                    (at ! each (|>> try.trusted console.async)))]
        ...       (interpreter.run! (try.with async.monad) console platform interpretation generation_bundle)))
        ))))