aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/meta/compiler/language/lux/phase/generation/lua/loop.lux
blob: bef9f98939915d16771c77d828c8ebb0d30361ac (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
(.require
 [library
  [lux (.except Label Scope)
   [abstract
    ["[0]" monad (.only do)]]
   [data
    ["[0]" product]
    [text
     ["%" \\format (.only format)]]
    [collection
     ["[0]" list (.use "[1]#[0]" functor)]
     ["[0]" set]]]
   [math
    [number
     ["n" nat]]]
   [meta
    [target
     ["_" lua (.only Var Expression Label Statement)]]]]]
 ["[0]" //
  [runtime (.only Operation Phase Phase! Generator Generator!)]
  ["[1][0]" case]
  ["/[1]" //
   ["[1][0]" reference]
   ["//[1]" ///
    ["[0]"synthesis (.only Scope Synthesis)]
    ["[1][0]" generation]
    ["//[1]" ///
     ["[1][0]" phase]
     [meta
      [archive (.only Archive)]
      ["[0]" cache
       [dependency
        ["[1]" artifact]]]]
     [reference
      [variable (.only Register)]]]]]])

(def @scope
  (-> Nat Label)
  (|>> %.nat (format "scope") _.label))

(def (setup initial? offset bindings as_expression? body)
  (-> Bit Register (List Expression) Bit Statement Statement)
  (let [variables (|> bindings
                      list.enumeration
                      (list#each (|>> product.left (n.+ offset) //case.register)))]
    (if as_expression?
      body
      (all _.then
           (if initial?
             (_.let variables (_.multi bindings))
             (_.set variables (_.multi bindings)))
           body))))

(def .public (scope! statement expression archive as_expression? [start initsS+ bodyS])
  ... (Generator! (Scope Synthesis))
  (-> Phase! Phase Archive Bit (Scope Synthesis)
      (Operation [(List Expression) Statement]))
  (case initsS+
    ... function/false/non-independent loop
    {.#End}
    (|> bodyS
        (statement expression archive)
        (at ///////phase.monad each (|>> [(list)])))

    ... true loop
    _
    (do [! ///////phase.monad]
      [@scope (at ! each ..@scope /////generation.next)
       initsO+ (monad.each ! (expression archive) initsS+)
       body! (/////generation.with_anchor [start @scope]
               (statement expression archive bodyS))]
      (in [initsO+
           (..setup true start initsO+ as_expression?
                    (all _.then
                         (_.set_label @scope)
                         body!))]))))

(def .public (scope statement expression archive [start initsS+ bodyS])
  (-> Phase! (Generator (Scope Synthesis)))
  (case initsS+
    ... function/false/non-independent loop
    {.#End}
    (expression archive bodyS)

    ... true loop
    _
    (do [! ///////phase.monad]
      [dependencies (cache.dependencies archive bodyS)
       [[artifact_module artifact_id] [initsO+ scope!]] (/////generation.with_new_context archive dependencies
                                                          (scope! statement expression archive true [start initsS+ bodyS]))
       .let [@loop (_.var (///reference.artifact [artifact_module artifact_id]))
             locals (|> initsO+
                        list.enumeration
                        (list#each (|>> product.left (n.+ start) //case.register)))
             [declaration instantiation] (is [Statement Expression]
                                             (case (|> (synthesis.path/then bodyS)
                                                       //case.dependencies
                                                       (set.of_list _.hash)
                                                       (set.difference (set.of_list _.hash locals))
                                                       set.list)
                                               {.#End}
                                               [(_.function @loop locals
                                                  scope!)
                                                @loop]

                                               foreigns
                                               (let [@context (_.var (format (_.code @loop) "_context"))]
                                                 [(_.function @context foreigns
                                                    (all _.then
                                                         (<| (_.local_function @loop locals)
                                                             scope!)
                                                         (_.return @loop)
                                                         ))
                                                  (_.apply foreigns @context)])))]
       _ (/////generation.execute! declaration)
       _ (/////generation.save! artifact_id {.#None} declaration)]
      (in (_.apply initsO+ instantiation)))))

(def .public (again! statement expression archive argsS+)
  (Generator! (List Synthesis))
  (do [! ///////phase.monad]
    [[offset @scope] /////generation.anchor
     argsO+ (monad.each ! (expression archive) argsS+)]
    (in (..setup false offset argsO+ false (_.go_to @scope)))))