78e3545b6ddf0eedd4f52c9c5fde3cadb2596b02
[hs-java.git] / JVM / Builder / Instructions.hs
1 -- | This module exports shortcuts for some of JVM instructions (which are defined in JVM.Assembler).
2 -- These functions get Constants, put them into constants pool and generate instruction using index
3 -- of constant in the pool.
4 module JVM.Builder.Instructions where
5
6 import Data.Word
7 import qualified Data.ByteString.Lazy as B
8
9 import JVM.ClassFile
10 import JVM.Assembler
11 import JVM.Builder.Monad
12
13 nop ::  Generate ()
14 nop = i0 NOP
15 aconst_null ::  Generate ()
16 aconst_null = i0 ACONST_NULL
17 iconst_m1 ::  Generate ()
18 iconst_m1 = i0 ICONST_M1
19 iconst_0 ::  Generate ()
20 iconst_0 = i0 ICONST_0
21 iconst_1 ::  Generate ()
22 iconst_1 = i0 ICONST_1
23 iconst_2 ::  Generate ()
24 iconst_2 = i0 ICONST_2
25 iconst_3 ::  Generate ()
26 iconst_3 = i0 ICONST_3
27 iconst_4 ::  Generate ()
28 iconst_4 = i0 ICONST_4
29 iconst_5 ::  Generate ()
30 iconst_5 = i0 ICONST_5
31 lconst_0 ::  Generate ()
32 lconst_0 = i0 LCONST_0
33 lconst_1 ::  Generate ()
34 lconst_1 = i0 LCONST_1
35 fconst_0 ::  Generate ()
36 fconst_0 = i0 FCONST_0
37 fconst_1 ::  Generate ()
38 fconst_1 = i0 FCONST_1
39 fconst_2 ::  Generate ()
40 fconst_2 = i0 FCONST_2
41 dconst_0 ::  Generate ()
42 dconst_0 = i0 DCONST_0
43 dconst_1 ::  Generate ()
44 dconst_1 = i0 DCONST_1
45
46 bipush ::  Word8 -> Generate ()
47 bipush x = i0 (BIPUSH x)
48 sipush ::  Word16 -> Generate ()
49 sipush x = i0 (SIPUSH x)
50
51 ldc1 ::  Constant Resolved -> Generate ()
52 ldc1 x = i8 LDC1 x
53 ldc2 ::  Constant Resolved -> Generate ()
54 ldc2 x = i1 LDC2 x
55 ldc2w ::  Constant Resolved -> Generate ()
56 ldc2w x = i1 LDC2W x
57 iload ::  Constant Resolved -> Generate ()
58 iload x = i8 ILOAD x
59 lload ::  Constant Resolved -> Generate ()
60 lload x = i8 LLOAD x
61 fload ::  Constant Resolved -> Generate ()
62 fload x = i8 FLOAD x
63 dload ::  Constant Resolved -> Generate ()
64 dload x = i8 DLOAD x
65 aload ::  Constant Resolved -> Generate ()
66 aload x = i8 ALOAD x
67
68 iload_ ::  IMM -> Generate ()
69 iload_ x = i0 (ILOAD_ x)
70 lload_ ::  IMM -> Generate ()
71 lload_ x = i0 (LLOAD_ x)
72 fload_ ::  IMM -> Generate ()
73 fload_ x = i0 (FLOAD_ x)
74 dload_ ::  IMM -> Generate ()
75 dload_ x = i0 (DLOAD_ x)
76 aload_ ::  IMM -> Generate ()
77 aload_ x = i0 (ALOAD_ x)
78
79 iaload ::  Generate ()
80 iaload = i0 IALOAD
81 laload ::  Generate ()
82 laload = i0 LALOAD
83 faload ::  Generate ()
84 faload = i0 FALOAD
85 daload ::  Generate ()
86 daload = i0 DALOAD
87 aaload ::  Generate ()
88 aaload = i0 AALOAD
89 caload ::  Generate ()
90 caload = i0 CALOAD
91 saload ::  Generate ()
92 saload = i0 SALOAD
93
94 istore ::  Constant Resolved -> Generate ()
95 istore x = i8 ISTORE x
96 lstore ::  Constant Resolved -> Generate ()
97 lstore x = i8 LSTORE x
98 fstore ::  Constant Resolved -> Generate ()
99 fstore x = i8 FSTORE x
100 dstore ::  Constant Resolved -> Generate ()
101 dstore x = i8 DSTORE x
102 astore ::  Constant Resolved -> Generate ()
103 astore x = i8 ASTORE x
104
105 istore_ ::  Word8 -> Generate ()
106 istore_ x = i0 (ISTORE x)
107 lstore_ ::  Word8 -> Generate ()
108 lstore_ x = i0 (LSTORE x)
109 fstore_ ::  Word8 -> Generate ()
110 fstore_ x = i0 (FSTORE x)
111 dstore_ ::  Word8 -> Generate ()
112 dstore_ x = i0 (DSTORE x)
113 astore_ ::  Word8 -> Generate ()
114 astore_ x = i0 (ASTORE x)
115
116 iastore ::  Generate ()
117 iastore = i0 IASTORE
118 lastore ::  Generate ()
119 lastore = i0 LASTORE
120 fastore ::  Generate ()
121 fastore = i0 FASTORE
122 dastore ::  Generate ()
123 dastore = i0 DASTORE
124 aastore ::  Generate ()
125 aastore = i0 AASTORE
126 bastore ::  Generate ()
127 bastore = i0 BASTORE
128 castore ::  Generate ()
129 castore = i0 CASTORE
130 sastore ::  Generate ()
131 sastore = i0 SASTORE
132
133 pop ::  Generate ()
134 pop     = i0 POP    
135 pop2 ::  Generate ()
136 pop2    = i0 POP2   
137 dup ::  Generate ()
138 dup     = i0 DUP    
139 dup_x1 ::  Generate ()
140 dup_x1  = i0 DUP_X1 
141 dup_x2 ::  Generate ()
142 dup_x2  = i0 DUP_X2 
143 dup2 ::  Generate ()
144 dup2    = i0 DUP2   
145 dup2_x1 ::  Generate ()
146 dup2_x1 = i0 DUP2_X1
147 dup2_x2 ::  Generate ()
148 dup2_x2 = i0 DUP2_X2
149 swap ::  Generate ()
150 swap    = i0 SWAP   
151 iadd ::  Generate ()
152 iadd    = i0 IADD   
153 ladd ::  Generate ()
154 ladd    = i0 LADD   
155 fadd ::  Generate ()
156 fadd    = i0 FADD   
157 dadd ::  Generate ()
158 dadd    = i0 DADD   
159 isub ::  Generate ()
160 isub    = i0 ISUB   
161 lsub ::  Generate ()
162 lsub    = i0 LSUB   
163 fsub ::  Generate ()
164 fsub    = i0 FSUB   
165 dsub ::  Generate ()
166 dsub    = i0 DSUB   
167 imul ::  Generate ()
168 imul    = i0 IMUL   
169 lmul ::  Generate ()
170 lmul    = i0 LMUL   
171 fmul ::  Generate ()
172 fmul    = i0 FMUL   
173 dmul ::  Generate ()
174 dmul    = i0 DMUL   
175 idiv ::  Generate ()
176 idiv    = i0 IDIV   
177 ldiv ::  Generate ()
178 ldiv    = i0 LDIV   
179 fdiv ::  Generate ()
180 fdiv    = i0 FDIV   
181 ddiv ::  Generate ()
182 ddiv    = i0 DDIV   
183 irem ::  Generate ()
184 irem    = i0 IREM   
185 lrem ::  Generate ()
186 lrem    = i0 LREM   
187 frem ::  Generate ()
188 frem    = i0 FREM   
189 drem ::  Generate ()
190 drem    = i0 DREM   
191 ineg ::  Generate ()
192 ineg    = i0 INEG   
193 lneg ::  Generate ()
194 lneg    = i0 LNEG   
195 fneg ::  Generate ()
196 fneg    = i0 FNEG   
197 dneg ::  Generate ()
198 dneg    = i0 DNEG   
199 ishl ::  Generate ()
200 ishl    = i0 ISHL   
201 lshl ::  Generate ()
202 lshl    = i0 LSHL   
203 ishr ::  Generate ()
204 ishr    = i0 ISHR   
205 lshr ::  Generate ()
206 lshr    = i0 LSHR   
207 iushr ::  Generate ()
208 iushr   = i0 IUSHR  
209 lushr ::  Generate ()
210 lushr   = i0 LUSHR  
211 iand ::  Generate ()
212 iand    = i0 IAND   
213 land ::  Generate ()
214 land    = i0 LAND   
215 ior ::  Generate ()
216 ior     = i0 IOR    
217 lor ::  Generate ()
218 lor     = i0 LOR    
219 ixor ::  Generate ()
220 ixor    = i0 IXOR   
221 lxor ::  Generate ()
222 lxor    = i0 LXOR   
223
224 iinc ::  Word8 -> Word8 -> Generate ()
225 iinc x y = i0 (IINC x y)
226
227 i2l ::  Generate ()
228 i2l  = i0 I2L 
229 i2f ::  Generate ()
230 i2f  = i0 I2F 
231 i2d ::  Generate ()
232 i2d  = i0 I2D 
233 l2i ::  Generate ()
234 l2i  = i0 L2I 
235 l2f ::  Generate ()
236 l2f  = i0 L2F 
237 l2d ::  Generate ()
238 l2d  = i0 L2D 
239 f2i ::  Generate ()
240 f2i  = i0 F2I 
241 f2l ::  Generate ()
242 f2l  = i0 F2L 
243 f2d ::  Generate ()
244 f2d  = i0 F2D 
245 d2i ::  Generate ()
246 d2i  = i0 D2I 
247 d2l ::  Generate ()
248 d2l  = i0 D2L 
249 d2f ::  Generate ()
250 d2f  = i0 D2F 
251 i2b ::  Generate ()
252 i2b  = i0 I2B 
253 i2c ::  Generate ()
254 i2c  = i0 I2C 
255 i2s ::  Generate ()
256 i2s  = i0 I2S 
257 lcmp ::  Generate ()
258 lcmp = i0 LCMP
259
260 -- | Wide instruction
261 wide :: (Word8 -> Instruction) -> Constant Resolved -> Generate ()
262 wide fn c = do
263   ix <- addToPool c
264   let ix0 = fromIntegral (ix `div` 0x100) :: Word8
265       ix1 = fromIntegral (ix `mod` 0x100) :: Word8
266   i0 (WIDE ix0 $ fn ix1)
267
268 new ::  B.ByteString -> Generate ()
269 new cls =
270   i1 NEW (CClass cls)
271
272 newArray ::  ArrayType -> Generate ()
273 newArray t =
274   i0 (NEWARRAY $ atype2byte t)
275
276 allocNewArray ::  B.ByteString -> Generate ()
277 allocNewArray cls =
278   i1 ANEWARRAY (CClass cls)
279
280 invokeVirtual ::  B.ByteString -> NameType Method -> Generate ()
281 invokeVirtual cls sig =
282   i1 INVOKEVIRTUAL (CMethod cls sig)
283
284 invokeStatic ::  B.ByteString -> NameType Method -> Generate ()
285 invokeStatic cls sig =
286   i1 INVOKESTATIC (CMethod cls sig)
287
288 invokeSpecial ::  B.ByteString -> NameType Method -> Generate ()
289 invokeSpecial cls sig =
290   i1 INVOKESPECIAL (CMethod cls sig)
291
292 getStaticField ::  B.ByteString -> NameType Field -> Generate ()
293 getStaticField cls sig =
294   i1 GETSTATIC (CField cls sig)
295
296 loadString ::  B.ByteString -> Generate ()
297 loadString str =
298   i8 LDC1 (CString str)
299
300 allocArray ::  B.ByteString -> Generate ()
301 allocArray cls =
302   i1 ANEWARRAY (CClass cls)
303