aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/program/compositor.lux
blob: 840b06e2d99d2f4751a1d97c7ebbf15772ccd377 (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
(.module:
  [library
   [lux {"-" [Module]}
    [type {"+" [:sharing]}]
    ["@" target]
    ["[0]" debug]
    [abstract
     [monad {"+" [do]}]]
    [control
     ["[0]" io {"+" [IO io]}]
     ["[0]" try {"+" [Try]}]
     [concurrency
      ["[0]" async {"+" [Async]} ("[1]#[0]" monad)]]]
    [data
     [binary {"+" [Binary]}]
     ["[0]" product]
     ["[0]" text
      ["%" format {"+" [format]}]]
     [collection
      ["[0]" dictionary {"+" [Dictionary]}]
      ["[0]" row {"+" [Row]}]]]
    [time
     ["[0]" instant]]
    ["[0]" world "_"
     ["[0]" file]
     ["[1]/[0]" program]
     ... ["[0]" console]
     ]
    [tool
     [compiler
      ["[0]" phase]
      [default
       ["[0]" platform {"+" [Platform]}]]
      [language
       ["$" lux
        ["[1]/[0]" program {"+" [Program]}]
        ["[0]" syntax]
        ["[0]" analysis
         [macro {"+" [Expander]}]]
        ["[0]" generation {"+" [Buffer Context]}]
        ["[0]" directive]
        [phase
         [extension {"+" [Extender]}]]]]
      [meta
       [packager {"+" [Packager]}]
       [archive {"+" [Archive]}
        [descriptor {"+" [Module]}]]
       [cache
        ["[0]" dependency]]
       [io
        ["ioW" archive]]]]
     ... ["[0]" interpreter]
     ]]]
  ["[0]" / "_"
   ["[1][0]" cli {"+" [Service]}]
   ["[1][0]" static {"+" [Static]}]
   ["[1][0]" export]
   ["[1][0]" import]])

(def: (or_crash! failure_description action)
  (All (_ a)
    (-> Text (Async (Try a)) (Async a)))
  (do async.monad
    [?output action]
    (case ?output
      {try.#Failure error}
      (exec (debug.log! (format text.new_line
                                failure_description text.new_line
                                error text.new_line))
        (io.run! (# world/program.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] static archive context)
  (-> (file.System Async) (Dictionary file.Path Binary) [Packager file.Path] Static Archive Context (Async (Try Any)))
  (case (packager host_dependencies archive context)
    {try.#Success content}
    (# fs write content package)
    
    {try.#Failure error}
    (# 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 [pending host_dependencies
           output (: (Dictionary file.Path Binary)
                     (dictionary.empty text.hash))]
      (case pending
        {.#End}
        (in output)

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

(with_expansions [<parameters> (as_is anchor expression artifact)]
  (def: .public (compiler static
                          expander host_analysis platform generation_bundle host_directive_bundle program anchorT,expressionT,directiveT extender
                          service
                          packager,package)
    (All (_ <parameters>)
      (-> Static
          Expander
          analysis.Bundle
          (IO (Platform <parameters>))
          (generation.Bundle <parameters>)
          (-> phase.Wrapper (directive.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_sources compilation_host_dependencies compilation_libraries compilation_target compilation_module] compilation]
               import (/import.import (value@ platform.#&file_system platform) compilation_libraries)
               [state archive phase_wrapper] (:sharing [<parameters>]
                                                       (Platform <parameters>)
                                                       platform
                                                       
                                                       (Async (Try [(directive.State+ <parameters>)
                                                                    Archive
                                                                    phase.Wrapper]))
                                                       (:expected (platform.initialize static compilation_module expander host_analysis platform generation_bundle host_directive_bundle program anchorT,expressionT,directiveT extender
                                                                                       import compilation_sources)))
               [archive state] (:sharing [<parameters>]
                                         (Platform <parameters>)
                                         platform
                                         
                                         (Async (Try [Archive (directive.State+ <parameters>)]))
                                         (:expected (platform.compile phase_wrapper import static expander platform compilation [archive state])))
               _ (ioW.freeze (value@ platform.#&file_system platform) static archive)
               program_context (async#in ($/program.context archive))
               host_dependencies (..load_host_dependencies (value@ platform.#&file_system platform) compilation_host_dependencies)
               _ (..package! (for [@.old (file.async file.default)
                                   @.jvm (file.async file.default)
                                   @.js file.default])
                             host_dependencies
                             packager,package
                             static
                             archive
                             program_context)]
              (in (debug.log! "Compilation complete!"))))

        {/cli.#Export export}
        (<| (or_crash! "Export failed:")
            (do (try.with async.monad)
              [_ (/export.export (value@ 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
        ...                    (# ! each (|>> try.trusted console.async)))]
        ...       (interpreter.run! (try.with async.monad) console platform interpretation generation_bundle)))
        ))))