aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/lux/compiler/default/phase/synthesis/expression.lux
blob: 0ab38afac1546f8d246a09c676f94e14ebfcc91e (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
(.module:
  [lux (#- primitive)
   [control
    ["." monad (#+ do)]]
   [data
    ["." maybe]
    [collection
     ["." list ("list/." Functor<List>)]
     ["dict" dictionary (#+ Dictionary)]]]]
  ["." // (#+ Synthesis Phase)
   ["." function]
   ["." case]
   ["/." // ("operation/." Monad<Operation>)
    ["." analysis (#+ Analysis)]
    ["." extension]
    [//
     ["." reference]]]])

(def: (primitive analysis)
  (-> analysis.Primitive //.Primitive)
  (case analysis
    #analysis.Unit
    (#//.Text //.unit)
    
    (^template [<analysis> <synthesis>]
      (<analysis> value)
      (<synthesis> value))
    ([#analysis.Bit  #//.Bit]
     [#analysis.Frac #//.F64]
     [#analysis.Text #//.Text])

    (^template [<analysis> <synthesis>]
      (<analysis> value)
      (<synthesis> (.i64 value)))
    ([#analysis.Nat #//.I64]
     [#analysis.Int #//.I64]
     [#analysis.Rev #//.I64])))

(def: #export (synthesize analysis)
  Phase
  (case analysis
    (#analysis.Primitive analysis')
    (operation/wrap (#//.Primitive (..primitive analysis')))

    (#analysis.Structure composite)
    (case (analysis.variant analysis)
      (#.Some variant)
      (do ///.Monad<Operation>
        [valueS (synthesize (get@ #analysis.value variant))]
        (wrap (#//.Structure (#//.Variant (set@ #analysis.value valueS variant)))))

      _
      (do ///.Monad<Operation>
        [tupleS (monad.map @ synthesize (analysis.tuple analysis))]
        (wrap (#//.Structure (#//.Tuple tupleS)))))

    (#analysis.Reference reference)
    (case reference
      (#reference.Constant constant)
      (operation/wrap (#//.Reference reference))

      (#reference.Variable var)
      (do ///.Monad<Operation>
        [resolver //.resolver]
        (case var
          (#reference.Local register)
          (do @
            [arity //.scope-arity]
            (wrap (if (function.nested? arity)
                    (if (n/= |0 register)
                      (|> (dec arity)
                          (list.n/range |1)
                          (list/map (|>> //.variable/local))
                          [(//.variable/local |0)]
                          //.function/apply)
                      (#//.Reference (#reference.Variable (function.adjust arity #0 var))))
                    (#//.Reference (#reference.Variable var)))))
          
          (#reference.Foreign register)
          (wrap (|> resolver (dict.get var) (maybe.default var) #reference.Variable #//.Reference)))))

    (#analysis.Case inputA branchesAB+)
    (case.synthesize (|>> synthesize //.indirectly) inputA branchesAB+)

    (#analysis.Apply _)
    (function.apply (|>> synthesize //.indirectly) analysis)

    (#analysis.Function environmentA bodyA)
    (function.function synthesize environmentA bodyA)

    (#analysis.Extension name args)
    (extension.apply (|>> synthesize //.indirectly)
                     [name args])
    ))