Added C and Ocaml bindings for functions, basic blocks, and
[oota-llvm.git] / test / Bindings / Ocaml / vmcore.ml
1 (* RUN: %ocamlc llvm.cma llvm_bitwriter.cma %s -o %t
2  * RUN: ./%t %t.bc
3  * RUN: llvm-dis < %t.bc > %t.ll
4  *)
5
6 (* Note: It takes several seconds for ocamlc to link an executable with
7          libLLVMCore.a, so it's better to write a big test than a bunch of
8          little ones. *)
9
10 open Llvm
11 open Llvm_bitwriter
12
13
14 (* Tiny unit test framework - really just to help find which line is busted *)
15 let exit_status = ref 0
16 let case_num = ref 0
17
18 let group name =
19   case_num := 0;
20   prerr_endline ("  " ^ name ^ "...")
21
22 let insist cond =
23   incr case_num;
24   let msg = if cond then "    pass " else begin
25     exit_status := 10;
26     "    FAIL "
27   end in
28   prerr_endline (msg ^ (string_of_int !case_num))
29
30 let suite name f =
31   prerr_endline (name ^ ":");
32   f ()
33
34
35 (*===-- Fixture -----------------------------------------------------------===*)
36
37 let filename = Sys.argv.(1)
38 let m = create_module filename
39
40
41 (*===-- Types -------------------------------------------------------------===*)
42
43 let test_types () =
44   (* RUN: grep {Ty01.*void} < %t.ll
45    *)
46   group "void";
47   insist (define_type_name "Ty01" void_type m);
48   insist (Void_type == classify_type void_type);
49
50   (* RUN: grep {Ty02.*i1} < %t.ll
51    *)
52   group "i1";
53   insist (define_type_name "Ty02" i1_type m);
54   insist (Integer_type == classify_type i1_type);
55
56   (* RUN: grep {Ty03.*i32} < %t.ll
57    *)
58   group "i32";
59   insist (define_type_name "Ty03" i32_type m);
60
61   (* RUN: grep {Ty04.*i42} < %t.ll
62    *)
63   group "i42";
64   let ty = make_integer_type 42 in
65   insist (define_type_name "Ty04" ty m);
66
67   (* RUN: grep {Ty05.*float} < %t.ll
68    *)
69   group "float";
70   insist (define_type_name "Ty05" float_type m);
71   insist (Float_type == classify_type float_type);
72
73   (* RUN: grep {Ty06.*double} < %t.ll
74    *)
75   group "double";
76   insist (define_type_name "Ty06" double_type m);
77   insist (Double_type == classify_type double_type);
78
79   (* RUN: grep {Ty07.*i32.*i1, double} < %t.ll
80    *)
81   group "function";
82   let ty = make_function_type i32_type [| i1_type; double_type |] false in
83   insist (define_type_name "Ty07" ty m);
84   insist (Function_type = classify_type ty);
85   insist (not (is_var_arg ty));
86   insist (i32_type == return_type ty);
87   insist (double_type == (param_types ty).(1));
88   
89   (* RUN: grep {Ty08.*\.\.\.} < %t.ll
90    *)
91   group "vararg";
92   let ty = make_function_type void_type [| i32_type |] true in
93   insist (define_type_name "Ty08" ty m);
94   insist (is_var_arg ty);
95   
96   (* RUN: grep {Ty09.*\\\[7 x i8\\\]} < %t.ll
97    *)
98   group "array";
99   let ty = make_array_type i8_type 7 in
100   insist (define_type_name "Ty09" ty m);
101   insist (7 = array_length ty);
102   insist (i8_type == element_type ty);
103   insist (Array_type == classify_type ty);
104   
105   (* RUN: grep {Ty10.*float\*} < %t.ll
106    *)
107   group "pointer";
108   let ty = make_pointer_type float_type in
109   insist (define_type_name "Ty10" ty m);
110   insist (float_type == element_type ty);
111   insist (Pointer_type == classify_type ty);
112   
113   (* RUN: grep {Ty11.*\<4 x i16\>} < %t.ll
114    *)
115   group "vector";
116   let ty = make_vector_type i16_type 4 in
117   insist (define_type_name "Ty11" ty m);
118   insist (i16_type == element_type ty);
119   insist (4 = vector_size ty);
120   
121   (* RUN: grep {Ty12.*opaque} < %t.ll
122    *)
123   group "opaque";
124   let ty = make_opaque_type () in
125   insist (define_type_name "Ty12" ty m);
126   insist (ty == ty);
127   insist (ty <> make_opaque_type ());
128   
129   (* RUN: grep -v {Ty13} < %t.ll
130    *)
131   group "delete";
132   let ty = make_opaque_type () in
133   insist (define_type_name "Ty13" ty m);
134   delete_type_name "Ty13" m
135
136
137 (*===-- Constants ---------------------------------------------------------===*)
138
139 let test_constants () =
140   (* RUN: grep {Const01.*i32.*-1} < %t.ll
141    *)
142   group "int";
143   let c = make_int_constant i32_type (-1) true in
144   ignore (define_global "Const01" c m);
145   insist (i32_type = type_of c);
146   insist (is_constant c);
147
148   (* RUN: grep {Const02.*i64.*-1} < %t.ll
149    *)
150   group "sext int";
151   let c = make_int_constant i64_type (-1) true in
152   ignore (define_global "Const02" c m);
153   insist (i64_type = type_of c);
154
155   (* RUN: grep {Const03.*i64.*4294967295} < %t.ll
156    *)
157   group "zext int64";
158   let c = make_int64_constant i64_type (Int64.of_string "4294967295") false in
159   ignore (define_global "Const03" c m);
160   insist (i64_type = type_of c);
161
162   (* RUN: grep {Const04.*"cruel\\\\00world"} < %t.ll
163    *)
164   group "string";
165   let c = make_string_constant "cruel\000world" false in
166   ignore (define_global "Const04" c m);
167   insist ((make_array_type i8_type 11) = type_of c);
168
169   (* RUN: grep {Const05.*"hi\\\\00again\\\\00"} < %t.ll
170    *)
171   group "string w/ null";
172   let c = make_string_constant "hi\000again" true in
173   ignore (define_global "Const05" c m);
174   insist ((make_array_type i8_type 9) = type_of c);
175
176   (* RUN: grep {Const06.*3.1459} < %t.ll
177    *)
178   group "real";
179   let c = make_real_constant double_type 3.1459 in
180   ignore (define_global "Const06" c m);
181   insist (double_type = type_of c);
182   
183   let one = make_int_constant i16_type 1 true in
184   let two = make_int_constant i16_type 2 true in
185   let three = make_int_constant i32_type 3 true in
186   let four = make_int_constant i32_type 4 true in
187   
188   (* RUN: grep {Const07.*\\\[ i32 3, i32 4 \\\]} < %t.ll
189    *)
190   group "array";
191   let c = make_array_constant i32_type [| three; four |] in
192   ignore (define_global "Const07" c m);
193   insist ((make_array_type i32_type 2) = (type_of c));
194   
195   (* RUN: grep {Const08.*< i16 1, i16 2.* >} < %t.ll
196    *)
197   group "vector";
198   let c = make_vector_constant [| one; two; one; two;
199                                   one; two; one; two |] in
200   ignore (define_global "Const08" c m);
201   insist ((make_vector_type i16_type 8) = (type_of c));
202   
203   (* RUN: grep {Const09.*\{ i16, i16, i32, i32 \} \{} < %t.ll
204    *)
205   group "structure";
206   let c = make_struct_constant [| one; two; three; four |] false in
207   ignore (define_global "Const09" c m);
208   insist ((make_struct_type [| i16_type; i16_type; i32_type; i32_type |] false)
209         = (type_of c));
210   
211   (* RUN: grep {Const10.*zeroinit} < %t.ll
212    *)
213   group "null";
214   let c = make_null (make_struct_type [| i1_type; i8_type;
215                                          i64_type; double_type |] true) in
216   ignore (define_global "Const10" c m);
217   
218   (* RUN: grep {Const11.*-1} < %t.ll
219    *)
220   group "all ones";
221   let c = make_all_ones i64_type in
222   ignore (define_global "Const11" c m);
223   
224   (* RUN: grep {Const12.*undef} < %t.ll
225    *)
226   group "undef";
227   let c = make_undef i1_type in
228   ignore (define_global "Const12" c m);
229   insist (i1_type = type_of c);
230   insist (is_undef c)
231
232
233 (*===-- Global Values -----------------------------------------------------===*)
234
235 let test_global_values () =
236   let (++) x f = f x; x in
237   let zero32 = make_null i32_type in
238
239   (* RUN: grep {GVal01} < %t.ll
240    *)
241   group "naming";
242   let g = define_global "TEMPORARY" zero32 m in
243   insist ("TEMPORARY" = value_name g);
244   set_value_name "GVal01" g;
245   insist ("GVal01" = value_name g);
246
247   (* RUN: grep {GVal02.*linkonce} < %t.ll
248    *)
249   group "linkage";
250   let g = define_global "GVal02" zero32 m ++
251           set_linkage Link_once_linkage in
252   insist (Link_once_linkage = linkage g);
253
254   (* RUN: grep {GVal03.*Hanalei} < %t.ll
255    *)
256   group "section";
257   let g = define_global "GVal03" zero32 m ++
258           set_section "Hanalei" in
259   insist ("Hanalei" = section g);
260   
261   (* RUN: grep {GVal04.*hidden} < %t.ll
262    *)
263   group "visibility";
264   let g = define_global "GVal04" zero32 m ++
265           set_visibility Hidden_visibility in
266   insist (Hidden_visibility = visibility g);
267   
268   (* RUN: grep {GVal05.*align 128} < %t.ll
269    *)
270   group "alignment";
271   let g = define_global "GVal05" zero32 m ++
272           set_alignment 128 in
273   insist (128 = alignment g)
274
275
276 (*===-- Global Variables --------------------------------------------------===*)
277
278 let test_global_variables () =
279   let (++) x f = f x; x in
280   let fourty_two32 = make_int_constant i32_type 42 false in
281
282   (* RUN: grep {GVar01.*external} < %t.ll
283    *)
284   group "declarations";
285   let g = declare_global i32_type "GVar01" m in
286   insist (is_declaration g);
287   
288   (* RUN: grep {GVar02.*42} < %t.ll
289    * RUN: grep {GVar03.*42} < %t.ll
290    *)
291   group "definitions";
292   let g = define_global "GVar02" fourty_two32 m in
293   let g2 = declare_global i32_type "GVar03" m ++
294            set_initializer fourty_two32 in
295   insist (not (is_declaration g));
296   insist (not (is_declaration g2));
297   insist ((global_initializer g) == (global_initializer g2));
298
299   (* RUN: grep {GVar04.*thread_local} < %t.ll
300    *)
301   group "threadlocal";
302   let g = define_global "GVar04" fourty_two32 m ++
303           set_thread_local true in
304   insist (is_thread_local g);
305
306   (* RUN: grep -v {GVar05} < %t.ll
307    *)
308   group "delete";
309   let g = define_global "GVar05" fourty_two32 m in
310   delete_global g
311
312
313 (*===-- Functions ---------------------------------------------------------===*)
314
315 let test_functions () =
316   let ty = make_function_type i32_type [| i32_type; i64_type |] false in
317   let pty = make_pointer_type ty in
318   
319   (* RUN: grep {declare i32 @Fn1\(i32, i64\)} < %t.ll
320    *)
321   group "declare";
322   let fn = declare_function "Fn1" ty m in
323   insist (pty = type_of fn);
324   insist (is_declaration fn);
325   insist (0 = Array.length (basic_blocks fn));
326   
327   (* RUN: grep -v {Fn2} < %t.ll
328    *)
329   group "delete";
330   let fn = declare_function "Fn2" ty m in
331   delete_function fn;
332   
333   (* RUN: grep {define.*Fn3} < %t.ll
334    *)
335   group "define";
336   let fn = define_function "Fn3" ty m in
337   insist (not (is_declaration fn));
338   insist (1 = Array.length (basic_blocks fn));
339   (* this function is not valid because init bb lacks a terminator *)
340   
341   (* RUN: grep {define.*Fn4.*Param1.*Param2} < %t.ll
342    *)
343   group "params";
344   let fn = define_function "Fn4" ty m in
345   let params = params fn in
346   insist (2 = Array.length params);
347   insist (params.(0) = param fn 0);
348   insist (params.(1) = param fn 1);
349   insist (i32_type = type_of params.(0));
350   insist (i64_type = type_of params.(1));
351   set_value_name "Param1" params.(0);
352   set_value_name "Param2" params.(1);
353   (* this function is not valid because init bb lacks a terminator *)
354   
355   (* RUN: grep {fastcc.*Fn5} < %t.ll
356    *)
357   group "callconv";
358   let fn = define_function "Fn5" ty m in
359   insist (ccc = function_call_conv fn);
360   set_function_call_conv fastcc fn;
361   insist (fastcc = function_call_conv fn)
362
363
364 (*===-- Basic Blocks ------------------------------------------------------===*)
365
366 let test_basic_blocks () =
367   let ty = make_function_type void_type [| |] false in
368   
369   (* RUN: grep {Bb1} < %t.ll
370    *)
371   group "entry";
372   let fn = declare_function "X" ty m in
373   let bb = append_block "Bb1" fn in
374   insist (bb = entry_block fn);
375   
376   (* RUN: grep -v Bb2 < %t.ll
377    *)
378   group "delete";
379   let fn = declare_function "X2" ty m in
380   let bb = append_block "Bb2" fn in
381   delete_block bb;
382   
383   group "insert";
384   let fn = declare_function "X3" ty m in
385   let bbb = append_block "" fn in
386   let bba = insert_block "" bbb in
387   insist ([| bba; bbb |] = basic_blocks fn);
388   
389   (* RUN: grep Bb3 < %t.ll
390    *)
391   group "name/value";
392   let fn = define_function "X4" ty m in
393   let bb = entry_block fn in
394   let bbv = value_of_block bb in
395   set_value_name "Bb3" bbv;
396   insist ("Bb3" = value_name bbv);
397   
398   group "casts";
399   let fn = define_function "X5" ty m in
400   let bb = entry_block fn in
401   insist (bb = block_of_value (value_of_block bb));
402   insist (value_is_block (value_of_block bb));
403   insist (not (value_is_block (make_null i32_type)))
404
405
406 (*===-- Builder -----------------------------------------------------------===*)
407
408 let test_builder () =
409   let (++) x f = f x; x in
410   
411   group "ret void";
412   begin
413     (* RUN: grep {ret void} < %t.ll
414      *)
415     let fty = make_function_type void_type [| |] false in
416     let fn = declare_function "X6" fty m in
417     let b = builder_at_end (append_block "Bb01" fn) in
418     ignore (build_ret_void b)
419   end;
420   
421   (* The rest of the tests will use one big function. *)
422   let fty = make_function_type i32_type [| i32_type; i32_type |] false in
423   let fn = define_function "X7" fty m in
424   let atentry = builder_at_end (entry_block fn) in
425   let p1 = param fn 0 ++ set_value_name "P1" in
426   let p2 = param fn 1 ++ set_value_name "P2" in
427   let f1 = build_uitofp p1 float_type "F1" atentry in
428   let f2 = build_uitofp p2 float_type "F2" atentry in
429   
430   let bb00 = append_block "Bb00" fn in
431   ignore (build_unreachable (builder_at_end bb00));
432   
433   group "ret"; begin
434     (* RUN: grep {ret.*P1} < %t.ll
435      *)
436     let ret = build_ret p1 atentry in
437     position_before ret atentry
438   end;
439   
440   group "br"; begin
441     (* RUN: grep {br.*Bb02} < %t.ll
442      *)
443     let bb02 = append_block "Bb02" fn in
444     let b = builder_at_end bb02 in
445     ignore (build_br bb02 b)
446   end;
447   
448   group "cond_br"; begin
449     (* RUN: grep {br.*Inst01.*Bb03.*Bb00} < %t.ll
450      *)
451     let bb03 = append_block "Bb03" fn in
452     let b = builder_at_end bb03 in
453     let cond = build_trunc p1 i1_type "Inst01" b in
454     ignore (build_cond_br cond bb03 bb00 b)
455   end;
456   
457   (* TODO: Switch *)
458   
459   group "invoke"; begin
460     (* RUN: grep {Inst02.*invoke.*P1.*P2} < %t.ll
461      * RUN: grep {to.*Bb04.*unwind.*Bb00} < %t.ll
462      *)
463     let bb04 = append_block "Bb04" fn in
464     let b = builder_at_end bb04 in
465     ignore (build_invoke fn [| p1; p2 |] bb04 bb00 "Inst02" b)
466   end;
467   
468   group "unwind"; begin
469     (* RUN: grep {unwind} < %t.ll
470      *)
471     let bb05 = append_block "Bb05" fn in
472     let b = builder_at_end bb05 in
473     ignore (build_unwind b)
474   end;
475   
476   group "unreachable"; begin
477     (* RUN: grep {unreachable} < %t.ll
478      *)
479     let bb06 = append_block "Bb06" fn in
480     let b = builder_at_end bb06 in
481     ignore (build_unreachable b)
482   end;
483   
484   group "arithmetic"; begin
485     let bb07 = append_block "Bb07" fn in
486     let b = builder_at_end bb07 in
487     
488     (* RUN: grep {Inst03.*add.*P1.*P2} < %t.ll
489      * RUN: grep {Inst04.*sub.*P1.*Inst03} < %t.ll
490      * RUN: grep {Inst05.*mul.*P1.*Inst04} < %t.ll
491      * RUN: grep {Inst06.*udiv.*P1.*Inst05} < %t.ll
492      * RUN: grep {Inst07.*sdiv.*P1.*Inst06} < %t.ll
493      * RUN: grep {Inst08.*fdiv.*F1.*F2} < %t.ll
494      * RUN: grep {Inst09.*urem.*P1.*Inst07} < %t.ll
495      * RUN: grep {Inst10.*srem.*P1.*Inst09} < %t.ll
496      * RUN: grep {Inst11.*frem.*F1.*Inst08} < %t.ll
497      * RUN: grep {Inst12.*shl.*P1.*Inst10} < %t.ll
498      * RUN: grep {Inst13.*lshr.*P1.*Inst12} < %t.ll
499      * RUN: grep {Inst14.*ashr.*P1.*Inst13} < %t.ll
500      * RUN: grep {Inst15.*and.*P1.*Inst14} < %t.ll
501      * RUN: grep {Inst16.*or.*P1.*Inst15} < %t.ll
502      * RUN: grep {Inst17.*xor.*P1.*Inst16} < %t.ll
503      * RUN: grep {Inst18.*sub.*0.*Inst17} < %t.ll
504      * RUN: grep {Inst19.*xor.*Inst18.*-1} < %t.ll
505      *)
506     let inst03 = build_add  p1 p2     "Inst03" b in
507     let inst04 = build_sub  p1 inst03 "Inst04" b in
508     let inst05 = build_mul  p1 inst04 "Inst05" b in
509     let inst06 = build_udiv p1 inst05 "Inst06" b in
510     let inst07 = build_sdiv p1 inst06 "Inst07" b in
511     let inst08 = build_fdiv f1 f2     "Inst08" b in
512     let inst09 = build_urem p1 inst07 "Inst09" b in
513     let inst10 = build_srem p1 inst09 "Inst10" b in
514           ignore(build_frem f1 inst08 "Inst11" b);
515     let inst12 = build_shl  p1 inst10 "Inst12" b in
516     let inst13 = build_lshr p1 inst12 "Inst13" b in
517     let inst14 = build_ashr p1 inst13 "Inst14" b in
518     let inst15 = build_and  p1 inst14 "Inst15" b in
519     let inst16 = build_or   p1 inst15 "Inst16" b in
520     let inst17 = build_xor  p1 inst16 "Inst17" b in
521     let inst18 = build_neg  inst17    "Inst18" b in
522          ignore (build_not  inst18    "Inst19" b)
523   end;
524   
525   group "memory"; begin
526     let bb08 = append_block "Bb08" fn in
527     let b = builder_at_end bb08 in
528     
529     (* RUN: grep {Inst20.*malloc.*i8    } < %t.ll
530      * RUN: grep {Inst21.*malloc.*i8.*P1} < %t.ll
531      * RUN: grep {Inst22.*alloca.*i32   } < %t.ll
532      * RUN: grep {Inst23.*alloca.*i32.*P2} < %t.ll
533      * RUN: grep {free.*Inst20} < %t.ll
534      * RUN: grep {Inst25.*load.*Inst21} < %t.ll
535      * RUN: grep {store.*P2.*Inst22} < %t.ll
536      * RUN: grep {Inst27.*getelementptr.*Inst23.*P2} < %t.ll
537      *)
538     let inst20 = build_malloc i8_type "Inst20" b in
539     let inst21 = build_array_malloc i8_type p1 "Inst21" b in
540     let inst22 = build_alloca i32_type "Inst22" b in
541     let inst23 = build_array_alloca i32_type p2 "Inst23" b in
542           ignore(build_free inst20 b);
543           ignore(build_load inst21 "Inst25" b);
544           ignore(build_store p2 inst22 b);
545           ignore(build_gep inst23 [| p2 |] "Inst27" b)
546   end;
547   
548   group "casts"; begin
549     let void_ptr = make_pointer_type i8_type in
550     
551     (* RUN: grep {Inst28.*trunc.*P1.*i8} < %t.ll
552      * RUN: grep {Inst29.*zext.*Inst28.*i32} < %t.ll
553      * RUN: grep {Inst30.*sext.*Inst29.*i64} < %t.ll
554      * RUN: grep {Inst31.*uitofp.*Inst30.*float} < %t.ll
555      * RUN: grep {Inst32.*sitofp.*Inst29.*double} < %t.ll
556      * RUN: grep {Inst33.*fptoui.*Inst31.*i32} < %t.ll
557      * RUN: grep {Inst34.*fptosi.*Inst32.*i64} < %t.ll
558      * RUN: grep {Inst35.*fptrunc.*Inst32.*float} < %t.ll
559      * RUN: grep {Inst36.*fpext.*Inst35.*double} < %t.ll
560      * RUN: grep {Inst37.*inttoptr.*P1.*i8\*} < %t.ll
561      * RUN: grep {Inst38.*ptrtoint.*Inst37.*i64} < %t.ll
562      * RUN: grep {Inst39.*bitcast.*Inst38.*double} < %t.ll
563      *)
564     let inst28 = build_trunc p1 i8_type "Inst28" atentry in
565     let inst29 = build_zext inst28 i32_type "Inst29" atentry in
566     let inst30 = build_sext inst29 i64_type "Inst30" atentry in
567     let inst31 = build_uitofp inst30 float_type "Inst31" atentry in
568     let inst32 = build_sitofp inst29 double_type "Inst32" atentry in
569           ignore(build_fptoui inst31 i32_type "Inst33" atentry);
570           ignore(build_fptosi inst32 i64_type "Inst34" atentry);
571     let inst35 = build_fptrunc inst32 float_type "Inst35" atentry in
572           ignore(build_fpext inst35 double_type "Inst36" atentry);
573     let inst37 = build_inttoptr p1 void_ptr "Inst37" atentry in
574     let inst38 = build_ptrtoint inst37 i64_type "Inst38" atentry in
575           ignore(build_bitcast inst38 double_type "Inst39" atentry)
576   end;
577   
578   group "comparisons"; begin
579     (* RUN: grep {Inst40.*icmp.*ne.*P1.*P2} < %t.ll
580      * RUN: grep {Inst41.*icmp.*sle.*P2.*P1} < %t.ll
581      * RUN: grep {Inst42.*fcmp.*false.*F1.*F2} < %t.ll
582      * RUN: grep {Inst43.*fcmp.*true.*F2.*F1} < %t.ll
583      *)
584     ignore (build_icmp Icmp_ne    p1 p2 "Inst40" atentry);
585     ignore (build_icmp Icmp_sle   p2 p1 "Inst41" atentry);
586     ignore (build_fcmp Fcmp_false f1 f2 "Inst42" atentry);
587     ignore (build_fcmp Fcmp_true  f2 f1 "Inst43" atentry)
588   end;
589   
590   group "miscellaneous"; begin
591     (* RUN: grep {Inst45.*call.*P2.*P1} < %t.ll
592      * RUN: grep {Inst47.*select.*Inst46.*P1.*P2} < %t.ll
593      * RUN: grep {Inst48.*va_arg.*null.*i32} < %t.ll
594      * RUN: grep {Inst49.*extractelement.*Vec1.*P2} < %t.ll
595      * RUN: grep {Inst50.*insertelement.*Vec1.*P1.*P2} < %t.ll
596      * RUN: grep {Inst51.*shufflevector.*Vec1.*Vec2.*Vec3} < %t.ll
597      *)
598     
599     (* TODO: %Inst44 = Phi *)
600     
601          ignore (build_call fn [| p2; p1 |] "Inst45" atentry);
602     let inst46 = build_icmp Icmp_eq p1 p2 "Inst46" atentry in
603          ignore (build_select inst46 p1 p2 "Inst47" atentry);
604          ignore (build_va_arg
605                   (make_null (make_pointer_type (make_pointer_type i8_type)))
606                   i32_type "Inst48" atentry);
607     
608     (* Set up some vector vregs. *)
609     let one = make_int_constant i32_type (-1) true in
610     let zero = make_int_constant i32_type 1 true in
611     let t1 = make_vector_constant [| one; zero; one; zero |] in
612     let t2 = make_vector_constant [| zero; one; zero; one |] in
613     let t3 = make_vector_constant [| one; one; zero; zero |] in
614     let vec1 = build_insertelement t1 p1 p2 "Vec1" atentry in
615     let vec2 = build_insertelement t2 p1 p2 "Vec2" atentry in
616     let vec3 = build_insertelement t3 p1 p2 "Vec3" atentry in
617     
618     ignore (build_extractelement vec1 p2 "Inst49" atentry);
619     ignore (build_insertelement vec1 p1 p2 "Inst50" atentry);
620     ignore (build_shufflevector vec1 vec2 vec3 "Inst51" atentry);
621   end
622
623
624 (*===-- Writer ------------------------------------------------------------===*)
625
626 let test_writer () =
627   group "writer";
628   insist (write_bitcode_file m filename);
629   
630   dispose_module m
631
632
633 (*===-- Driver ------------------------------------------------------------===*)
634
635 let _ =
636   suite "types"            test_types;
637   suite "constants"        test_constants;
638   suite "global values"    test_global_values;
639   suite "global variables" test_global_variables;
640   suite "functions"        test_functions;
641   suite "basic blocks"     test_basic_blocks;
642   suite "builder"          test_builder;
643   suite "writer"           test_writer;
644   exit !exit_status