aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/meta/compiler/language/lux/phase/translation/python/loop.lux
blob: d7a494c1a9f4bdb82fa71cd68efe52c6e9a98690 (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
... This Source Code Form is subject to the terms of the Mozilla Public License, v. 2.0.
... If a copy of the MPL was not distributed with this file, You can obtain one at https://mozilla.org/MPL/2.0/.

(.require
 [library
  [lux (.except Scope)
   [abstract
    ["[0]" monad (.only do)]]
   [data
    ["[0]" product]
    [text
     ["%" \\format (.only format)]]
    [collection
     ["[0]" list (.use "[1]#[0]" functor mix)]
     ["[0]" set]]]
   [math
    [number
     ["n" nat]]]
   [meta
    [compiler
     [target
      ["_" python (.only Expression SVar Statement)]]]]]]
 ["[0]" //
  [runtime (.only Operation Phase Translator Phase! Translator!)]
  ["[1][0]" when]
  ["/[1]" //
   ["[1][0]" reference]
   ["/[1]" //
    [synthesis
     ["[0]" when]]
    ["/[1]" //
     ["[0]" phase]
     ["[0]" synthesis (.only Scope)]
     ["[1][0]" translation]
     ["//[1]" ///
      [meta
       ["[0]" cache
        [dependency
         ["[1]" artifact]]]]
      [reference
       ["[1][0]" variable (.only Register)]]]]]]])

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

(def .public (set_scope body!)
  (-> (Statement Any) (Statement Any))
  (_.while (_.bool true)
           body!
           {.#None}))

(def .public (scope! statement expression archive [start initsS+ bodyS])
  (Translator! (Scope synthesis.Term))
  (when initsS+
    ... function/false/non-independent loop
    {.#End}
    (statement expression archive bodyS)

    ... true loop
    _
    (do [! phase.monad]
      [initsO+ (monad.each ! (expression archive) initsS+)
       body! (/////translation.with_anchor start
               (statement expression archive bodyS))]
      (in (<| (..setup start initsO+)
              ..set_scope
              body!)))))

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

    ... true loop
    _
    (do [! phase.monad]
      [dependencies (cache.dependencies archive bodyS)
       initsO+ (monad.each ! (expression archive) initsS+)
       [[loop_module loop_artifact] body!] (/////translation.with_new_context archive dependencies
                                             (/////translation.with_anchor start
                                               (statement expression archive bodyS)))
       .let [@loop (_.var (///reference.artifact [loop_module loop_artifact]))
             locals (|> initsS+
                        list.enumeration
                        (list#each (|>> product.left (n.+ start) //when.register)))
             actual_loop (<| (_.def @loop locals)
                             ..set_scope
                             body!)
             [declaration instantiation] (is [(Statement Any) (Expression Any)]
                                             (when (|> (synthesis.path/then bodyS)
                                                       //when.dependencies
                                                       (set.of_list _.hash)
                                                       (set.difference (set.of_list _.hash locals))
                                                       set.list)
                                               {.#End}
                                               [actual_loop
                                                @loop]

                                               foreigns
                                               [(_.def @loop foreigns
                                                  (all _.then
                                                       actual_loop
                                                       (_.return @loop)
                                                       ))
                                                (_.apply foreigns @loop)]))]
       _ (/////translation.execute! declaration)
       _ (/////translation.save! loop_artifact {.#None} declaration)]
      (in (_.apply initsO+ instantiation)))))

(def .public (again! statement expression archive argsS+)
  (Translator! (List synthesis.Term))
  (do [! phase.monad]
    [offset /////translation.anchor
     @temp (//when.symbol "lux_again_values")
     argsO+ (monad.each ! (expression archive) argsS+)
     .let [re_binds (|> argsO+
                        list.enumeration
                        (list#each (function (_ [idx _])
                                     (_.item (_.int (.int idx)) @temp))))]]
    (in (all _.then
             (_.set (list @temp) (_.list argsO+))
             (..setup offset re_binds
                      _.continue)))))