aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/ruby/function.lux
blob: 022b449f0f8a5e389d3587453e0a82b5508468c1 (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
(.module:
  [library
   [lux {"-" [Variant Tuple function]}
    [abstract
     ["." monad {"+" [do]}]]
    [data
     ["." product]
     [text
      ["%" format {"+" [format]}]]
     [collection
      ["." list ("#\." functor mix)]]]
    [target
     ["_" ruby {"+" [LVar GVar Expression Statement]}]]]]
  ["." // "_"
   [runtime {"+" [Operation Phase Generator Phase! Generator!]}]
   ["#." reference]
   ["#." case]
   ["#." loop]
   ["/#" // "_"
    ["#." reference]
    ["//#" /// "_"
     [analysis {"+" [Variant Tuple Environment Abstraction Application Analysis]}]
     [synthesis {"+" [Synthesis]}]
     ["#." generation {"+" [Context]}]
     ["//#" /// "_"
      [arity {"+" [Arity]}]
      ["#." phase]
      [reference
       [variable {"+" [Register Variable]}]]
      [meta
       [archive {"+" [Archive]}
        ["." artifact]]]]]]])

(def: .public (apply expression archive [functionS argsS+])
  (Generator (Application Synthesis))
  (do [! ///////phase.monad]
    [functionO (expression archive functionS)
     argsO+ (monad.each ! (expression archive) argsS+)]
    (in (_.apply_lambda/* argsO+ functionO))))

(def: .public capture
  (-> Register LVar)
  (|>> (///reference.foreign //reference.system) :expected))

(def: (with_closure inits self function_definition)
  (-> (List Expression) Text Expression [Statement Expression])
  (case inits
    #.End
    (let [@self (_.global self)]
      [(_.set (list @self) function_definition)
       @self])

    _
    (let [@self (_.local self)]
      [(_.function @self
         (|> (list.enumeration inits)
             (list\each (|>> product.left ..capture)))
         ($_ _.then
             (_.set (list @self) function_definition)
             (_.return @self)))
       (_.apply/* inits @self)])))

(def: input
  (|>> ++ //case.register))

(def: .public (function statement expression archive [environment arity bodyS])
  (-> Phase! (Generator (Abstraction Synthesis)))
  (do [! ///////phase.monad]
    [[[function_module function_artifact] body!] (/////generation.with_new_context archive
                                                   (/////generation.with_anchor 1
                                                     (statement expression archive bodyS)))
     closureO+ (monad.each ! (expression archive) environment)
     .let [function_name (///reference.artifact [function_module function_artifact])
           @curried (_.local "curried")
           arityO (|> arity .int _.int)
           limitO (|> arity -- .int _.int)
           @num_args (_.local "num_args")
           @self (_.local function_name)
           initialize_self! (_.set (list (//case.register 0)) @self)
           initialize! (list\mix (.function (_ post pre!)
                                   ($_ _.then
                                       pre!
                                       (_.set (list (..input post)) (_.item (|> post .int _.int) @curried))))
                                 initialize_self!
                                 (list.indices arity))
           [declaration instatiation] (with_closure closureO+ function_name
                                        (_.lambda (#.Some @self) (list (_.variadic @curried))
                                                  ($_ _.then
                                                      (_.set (list @num_args) (_.the "length" @curried))
                                                      (_.cond (list [(|> @num_args (_.= arityO))
                                                                     (<| (_.then initialize!)
                                                                         //loop.with_scope
                                                                         body!)]
                                                                    [(|> @num_args (_.> arityO))
                                                                     (let [slice (.function (_ from to)
                                                                                   (_.array_range from to @curried))
                                                                           arity_args (_.splat (slice (_.int +0) limitO))
                                                                           output_func_args (_.splat (slice arityO @num_args))]
                                                                       (_.return (|> @self
                                                                                     (_.apply_lambda/* (list arity_args))
                                                                                     (_.apply_lambda/* (list output_func_args)))))])
                                                              ... (|> @num_args (_.< arityO))
                                                              (let [@missing (_.local "missing")]
                                                                (_.return (_.lambda #.None (list (_.variadic @missing))
                                                                                    (_.return (|> @self
                                                                                                  (_.apply_lambda/* (list (_.splat (|> (_.array (list))
                                                                                                                                       (_.do "concat" (list @curried))
                                                                                                                                       (_.do "concat" (list @missing))))))))))))
                                                      )))]
     _ (/////generation.execute! declaration)
     _ (/////generation.save! function_artifact #.None declaration)]
    (in instatiation)))