aboutsummaryrefslogtreecommitdiff
path: root/stdlib/source/library/lux/tool/compiler/language/lux/phase/generation/jvm/function/method/init.lux
blob: 2613bda11e045a04525acf1ca63e95400e045c10 (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
(.using
 [library
  [lux {"-" Type type}
   [abstract
    ["[0]" monad]]
   [control
    ["[0]" try]]
   [data
    [collection
     ["[0]" list ("[1]#[0]" monoid functor)]]]
   [math
    [number
     ["n" nat]]]
   [target
    [jvm
     ["_" bytecode (.only Bytecode)]
     ["[0]" method (.only Method)]
     [encoding
      ["[0]" signed]]
     [constant
      [pool (.only Resource)]]
     ["[0]" type (.only Type)
      ["[0]" category (.only Class Value)]]]]]]
 ["[0]" //
  ["[1][0]" implementation]
  ["/[1]" // "_"
   ["[1][0]" abstract]
   [field
    [constant
     ["[1][0]" arity]]
    [variable
     ["[1][0]" foreign]
     ["[1][0]" partial]]]
   ["/[1]" // "_"
    ["[1][0]" type]
    ["[1][0]" reference]
    [////
     [analysis (.only Environment)]
     [synthesis (.only Synthesis)]
     [///
      ["[0]" arity (.only Arity)]
      [reference
       [variable (.only Register)]]]]]]])

(def: .public name "<init>")

(def: (partials arity)
  (-> Arity (List (Type Value)))
  (list.repeated (-- arity) ////type.value))

(def: .public (type environment arity)
  (-> (Environment Synthesis) Arity (Type category.Method))
  (type.method [(list)
                (list#composite (///foreign.closure environment)
                                (if (arity.multiary? arity)
                                  (partial_list ///arity.type (..partials arity))
                                  (list)))
                type.void
                (list)]))

(def: no_partials
  (|> +0
      signed.s1
      try.trusted
      _.bipush))

(def: .public (super environment_size arity)
  (-> Nat Arity (Bytecode Any))
  (let [arity_register (++ environment_size)]
    (all _.composite
         (if (arity.unary? arity)
           ..no_partials
           (_.iload arity_register))
         (_.invokespecial ///abstract.class ..name ///abstract.init))))

(def: (store_all amount put offset)
  (-> Nat
      (-> Register (Bytecode Any) (Bytecode Any))
      (-> Register Register)
      (Bytecode Any))
  (|> (list.indices amount)
      (list#each (function (_ register)
                   (put register
                        (_.aload (offset register)))))
      (monad.all _.monad)))

(def: .public (method class environment arity)
  (-> (Type Class) (Environment Synthesis) Arity (Resource Method))
  (let [environment_size (list.size environment)
        offset_foreign (is (-> Register Register)
                           (n.+ 1))
        offset_arity (is (-> Register Register)
                         (|>> offset_foreign (n.+ environment_size)))
        offset_partial (is (-> Register Register)
                           (|>> offset_arity (n.+ 1)))]
    (method.method //.modifier ..name
                   #0 (..type environment arity)
                   (list)
                   {.#Some (all _.composite
                                ////reference.this
                                (..super environment_size arity)
                                (store_all environment_size (///foreign.put class) offset_foreign)
                                (store_all (-- arity) (///partial.put class) offset_partial)
                                _.return)})))