-
Notifications
You must be signed in to change notification settings - Fork 31
/
reloc.ml
1559 lines (1410 loc) · 48.2 KB
/
reloc.ml
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
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
894
895
896
897
898
899
900
901
902
903
904
905
906
907
908
909
910
911
912
913
914
915
916
917
918
919
920
921
922
923
924
925
926
927
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
944
945
946
947
948
949
950
951
952
953
954
955
956
957
958
959
960
961
962
963
964
965
966
967
968
969
970
971
972
973
974
975
976
977
978
979
980
981
982
983
984
985
986
987
988
989
990
991
992
993
994
995
996
997
998
999
1000
(************************************************************************)
(* FlexDLL *)
(* Alain Frisch *)
(* *)
(* Copyright 2007 Institut National de Recherche en Informatique et *)
(* en Automatique. *)
(************************************************************************)
(* The main application: parse COFF files,
compute relocation and export tables, rewrite some COFF files,
call the native linker *)
open Compat
open Coff
open Cmdline
let debug ?(dry_mode = {contents=false}) min_level fmt =
let print msg =
if !dry_mode || !verbose >= min_level then
Printf.printf "%s\n%!" msg
in
Printf.ksprintf print fmt
let search_path = ref []
let default_libs = ref []
let gcc = ref "gcc"
let objdump = ref "objdump"
let is_crt_lib = function
| "LIBCMT"
| "MSVCRT" -> true
| _ -> false
let flexdir =
try
let s = Sys.getenv "FLEXDIR" in
if s = "" then raise Not_found else s
with Not_found ->
Filename.dirname Sys.executable_name
let ext_obj () =
if !toolchain = `MSVC || !toolchain = `MSVC64 then ".obj" else ".o"
(* Temporary files *)
let temps = ref []
let add_temp fn =
temps := fn :: !temps; fn
let temp_file s x =
add_temp (Filename.temp_file s x)
let open_temp_file s x =
let (f, c) = Filename.open_temp_file s x in (add_temp f, c)
let safe_remove s =
try Sys.remove s
with Sys_error _ -> ()
let () =
at_exit
(fun () -> if not !save_temps then List.iter safe_remove !temps)
(* Calling external commands *)
let read_file fn =
let ic = open_in fn in
let r = ref [] in
(try while true do r := input_line ic :: !r done with End_of_file -> ());
close_in ic;
List.rev !r
(* This is the longest command which can be passed to [Sys.command] *)
let max_command_length =
let processor = try Sys.getenv "COMSPEC" with Not_found -> "cmd.exe" in
(* The 4 is from the " /c " *)
8191 - String.length processor - 4
let get_output ?(use_bash = false) ?(accept_error=false) cmd =
let fn = Filename.temp_file "flexdll" "" in
let cmd' = cmd ^ " > " ^ (Filename.quote fn) in
if String.length cmd' <= max_command_length && not use_bash then
begin
if (Sys.command cmd' <> 0) && not accept_error
then failwith ("Cannot run " ^ cmd);
end
else
begin
let (cfn, oc) = open_temp_file "longcmd" ".sh" in
output_string oc cmd'; close_out oc;
if Sys.command (Printf.sprintf "bash %s" cfn) <> 0
then failwith ("Cannot run " ^ cmd)
end;
let r = read_file fn in
Sys.remove fn;
r
let get_output1 ?use_bash ?accept_error fmt =
Printf.ksprintf (fun cmd ->
match get_output ?use_bash ?accept_error cmd with
| output::_ -> output
| [] -> raise (Failure ("command " ^ cmd ^ " did not return any output"))) fmt
let get_output ?use_bash ?accept_error fmt =
Printf.ksprintf (get_output ?use_bash ?accept_error) fmt
(* Preparing command line *)
let mk_dirs_opt pr = String.concat " " (List.map (fun s -> pr ^ (Filename.quote s)) !dirs)
exception Not_utf8
let utf8_next s i =
let fail () = raise Not_utf8 in
let check i =
if i >= String.length s then fail ();
let n = Char.code s.[i] in
if n lsr 6 <> 0b10 then fail () else n
in
if !i >= String.length s then fail ();
match s.[!i] with
| '\000'..'\127' as c ->
let n = Char.code c in
i := !i + 1;
n
| '\192'..'\223' as c ->
let n1 = Char.code c in
let n2 = check (!i+1) in
let n =
((n1 land 0b11111) lsl 6) lor
((n2 land 0b111111))
in
i := !i + 2;
n
| '\224'..'\239' as c ->
let n1 = Char.code c in
let n2 = check (!i+1) in
let n3 = check (!i+2) in
let n =
((n1 land 0b1111) lsl 12) lor
((n2 land 0b111111) lsl 6) lor
((n3 land 0b111111))
in
i := !i + 3;
n
| '\240'..'\247' as c ->
let n1 = Char.code c in
let n2 = check (!i+1) in
let n3 = check (!i+2) in
let n4 = check (!i+3) in
let n =
((n1 land 0b111) lsl 18) lor
((n2 land 0b111111) lsl 12) lor
((n3 land 0b111111) lsl 6) lor
((n4 land 0b111111))
in
i := !i + 4;
n
| _ ->
fail ()
let toutf16 s =
let i = ref 0 in
let b = Buffer.create (String.length s * 2) in
while !i < String.length s do
Buffer.add_utf_16le_uchar b (Uchar.unsafe_of_int (utf8_next s i))
done;
Buffer.contents b
(* Build @responsefile to work around Windows limitations on
command-line length *)
let build_diversion lst =
let responsefile = temp_file "camlresp" "" in
let oc = open_out_bin responsefile in
let lst =
List.map (fun f ->
let s = Bytes.of_string (Filename.quote f) in
for i = 0 to Bytes.length s - 1 do
if Bytes.get s i = '\\' then Bytes.set s i '/'
done;
Bytes.to_string s ^ "\r\n"
) (List.filter (fun f -> f <> "") lst)
in
let utf16, lst =
try true, List.map toutf16 lst
with Not_utf8 -> false, lst
in
if utf16 then output_string oc "\xFF\xFE"; (* LE BOM *)
List.iter (fun s -> output_string oc s) lst;
close_out oc;
"@" ^ responsefile
type cmdline = {
may_use_response_file: bool;
}
let new_cmdline () =
let rf = match !toolchain with
| `MSVC | `MSVC64 | `LIGHTLD -> true
| `MINGW | `MINGW64 | `GNAT | `GNAT64 | `CYGWIN64 -> false
in
{
may_use_response_file = rf;
}
let run_command cmdline cmd =
let pipe_to_null = (!toolchain = `MSVC || !toolchain = `MSVC64) in
let silencer = if pipe_to_null then " >NUL 2>NUL" else ""
in
(* note: for Cygwin, using bash allow to follow symlinks to find
gcc... *)
if !toolchain = `CYGWIN64 ||
String.length cmd + String.length silencer > max_command_length
then begin
(* Dump the command in a text file and apply bash to it. *)
let (fn, oc) = open_temp_file "longcmd" "" in
output_string oc cmd;
if pipe_to_null then
output_string oc " &>/dev/null";
close_out oc;
debug 1 "(call with bash: %s)\n%!" fn;
let invoke = Printf.sprintf "bash %s" fn in
if Sys.command invoke <> 0 then begin
if pipe_to_null then begin
let oc = open_out fn in
output_string oc cmd;
close_out oc;
ignore (Sys.command invoke)
end;
failwith "Error during linking\n"
end
end else
if Sys.command (cmd ^ silencer) <> 0 then begin
if pipe_to_null then ignore (Sys.command cmd);
failwith "Error during linking\n"
end
let quote_files cmdline lst =
let s =
String.concat " "
(List.map (fun f -> if f = "" then f else Filename.quote f) lst) in
if String.length s >= 1024 && cmdline.may_use_response_file then Filename.quote (build_diversion lst)
else s
(* Looking for files *)
let cygpath l cont =
let accept_error = (!use_cygpath = `Try && l <> []) in
let l =
let args = String.concat " " (List.map Filename.quote l) in
get_output ~accept_error "cygpath -m %s" args
in
if accept_error && l = [] then begin
use_cygpath := `No;
None
end else
cont l
let cygpath1 fn =
let accept_error = (!use_cygpath = `Try) in
match get_output ~accept_error "cygpath -m %s" fn with
| output::_ ->
if accept_error then
use_cygpath := `Yes;
Some output
| [] when accept_error ->
use_cygpath := `No;
None
| [] ->
raise (Failure "cygpath did not return any output")
let file_exists fn =
if Sys.file_exists fn && not (Sys.is_directory fn) then Some fn
else if !use_cygpath <> `No && Sys.file_exists (fn ^ ".lnk") then
cygpath1 fn
else None
let dir_exists_no_cygpath fn =
Sys.file_exists fn && (try Sys.is_directory fn with Sys_error _ -> false)
let rec find_file_in = function
| [] -> None
| fn::rest ->
match file_exists fn with
| Some x -> Some x
| None -> find_file_in rest
let find_file suffixes fn =
let l =
List.flatten
(List.map
(fun dir ->
let fn = Filename.concat dir fn in
fn :: (List.map (fun suff -> fn ^ suff) suffixes)
) (""::!search_path)) in
match find_file_in l with
| Some x -> Some x
| None ->
if !use_cygpath <> `No then
cygpath l find_file_in
else None
let rec map_until_found f = function
| [] ->
None
| x::xs ->
match f x with
| None ->
map_until_found f xs
| r ->
r
let find_file =
let memo = Hashtbl.create 16 in
fun fn ->
let k = String.lowercase_ascii fn in
try Hashtbl.find memo k
with Not_found ->
try Hashtbl.find memo (k ^ ".lib")
with Not_found ->
let fns, suffixes =
(* XXX Not sure why we do these extensions for _both_ MSVC and
mingw-w64 rather than .lib for MSVC and the .a ones for
mingw-w64? *)
let standard_suffixes = [".lib"; ".dll.a"; ".a"] in
if String.length fn > 2 && String.sub fn 0 2 = "-l" then
let base = String.sub fn 2 (String.length fn - 2) in
if String.length base > 0 && base.[0] = ':' then
[String.sub base 1 (String.length base - 1)], []
else if !toolchain = `MSVC || !toolchain = `MSVC64 then
["lib" ^ base; base], standard_suffixes
else
["lib" ^ base], standard_suffixes
else [fn], standard_suffixes in
let r =
match map_until_found (find_file suffixes) fns with
| Some fn -> fn
| None ->
failwith (Printf.sprintf "Cannot find file %S" fn)
in
Hashtbl.add memo k r;
Hashtbl.add memo (k ^ ".lib") r;
r
(*******************************)
let int32_to_buf b i =
Buffer.add_char b (Char.chr (i land 0xff));
Buffer.add_char b (Char.chr ((i lsr 8) land 0xff));
Buffer.add_char b (Char.chr ((i lsr 16) land 0xff));
Buffer.add_char b (Char.chr ((i lsr 24) land 0xff))
let int_to_buf b i =
assert(i >= 0);
match !machine with
| `x86 -> int32_to_buf b i
| `x64 -> int32_to_buf b i; int32_to_buf b 0
let exportable s =
match !machine with
| `x86 ->
s <> "" && (s.[0] = '_' || s.[0] = '?')
| `x64 ->
if String.length s > 2 && s.[0] = '?' && s.[1] = '?' then false
else true
let drop_underscore obj s =
match !machine with
| `x86 ->
assert (s <> "");
begin
match s.[0] with
| '_' -> String.sub s 1 (String.length s - 1)
| '?' -> s
| _ -> failwith (Printf.sprintf "In %s, symbol %s doesn't start with _ or ?" obj.obj_name s)
end
| `x64 ->
s
let has_prefix pr s =
String.length s > String.length pr && String.sub s 0 (String.length pr) = pr
let check_prefix pr s =
if has_prefix pr s then
Some (String.sub s (String.length pr) (String.length s - String.length pr))
else None
let parse_libpath s =
let n = String.length s in
let rec aux l =
if l >= n then []
else
try
let i = String.index_from s l ';' in
String.sub s l (i - l) :: aux (succ i)
with Not_found -> [ String.sub s l (n - l) ]
in
aux 0
module StrSet = Set.Make(String)
(* Put all the relocations on the symbols defined by a predicate
into a relocation table. A relocation table describes how to
patch some addresses with the value of some external symbols (given
by their name). It also lists segments that are normally write-protected
and that must be de-protected to enable the patching process. *)
let add_reloc_table obj obj_name p =
let sname = Symbol.gen_sym () in (* symbol pointing to the reloc table *)
let sect = Section.create ".reltbl" 0xc0300040l in
let data = Buffer.create 1024 in
let strings = Buffer.create 1024 in
let nonwr = ref [] in
let nonwrsym = Symbol.intern sect 0l in
let strsym = Symbol.intern sect 0l in
let str_pos = Hashtbl.create 16 in
Reloc.abs !machine sect 0l nonwrsym;
int_to_buf data 0;
(* TODO: use a single symbol per section *)
let syms = ref [] in
let reloc secsym min max rel =
if p rel.symbol then (
(* kind *)
let kind = match !machine, rel.rtype with
| `x86, 0x06 (* IMAGE_REL_I386_DIR32 *)
| `x64, 0x01 (* IMAGE_REL_AMD64_ADDR64 *) ->
0x0002 (* absolute, native size (32/64) *)
| `x64, 0x04 (* IMAGE_REL_AMD64_REL32 *)
| `x86, 0x14 (* IMAGE_REL_I386_REL32 *) when not !no_rel_relocs ->
0x0001 (* rel32 *)
| `x64, 0x05 when not !no_rel_relocs -> 0x0004 (* rel32_1 *)
| `x64, 0x08 when not !no_rel_relocs-> 0x0003 (* rel32_4 *)
| `x64, 0x06 when not !no_rel_relocs-> 0x0005 (* rel32_2 *)
| (`x86 | `x64), (0x0a (* IMAGE_REL_{I386|AMD64}_SECTION *) |
0x0b (* IMAGE_REL_{I386|AMD64}_SECREL*) ) ->
0x0100 (* debug relocs: ignore *)
| _, k ->
let msg =
Printf.sprintf "Unsupported relocation kind %04x for %s in %s"
k rel.symbol.sym_name obj_name
in
failwith msg
(* Printf.eprintf "%s\n%!" msg;
0x0001 *)
in
int_to_buf data kind;
(* name *)
let name = drop_underscore obj rel.symbol.sym_name in
let pos =
try Hashtbl.find str_pos name
with Not_found ->
let pos = Buffer.length strings in
Hashtbl.add str_pos name pos;
Buffer.add_string strings name;
Buffer.add_char strings '\000';
pos
in
Reloc.abs !machine sect (Int32.of_int (Buffer.length data)) strsym;
int_to_buf data pos;
Reloc.abs !machine sect (Int32.of_int (Buffer.length data))
(Lazy.force secsym);
int_to_buf data (Int32.to_int rel.addr);
if rel.addr <= !min then min := rel.addr;
if rel.addr >= !max then max := rel.addr;
false
) else true
in
let section sec =
if sec.sec_opts &&& 0x1000l <> 0l && has_prefix ".rdata$.refptr." sec.sec_name then
begin
(* under Cygwin64, gcc introduces mergable (link once) COMDAT sections to store
indirection pointers to external darta symbols. Since we don't deal with such section
properly, we turn them into regular data section, thus loosing sharing (but we don't care). *)
sec.sec_opts <- 0xc0500040l;
sec.sec_name <- Printf.sprintf ".flexrefptrsection%i" (Oo.id (object end));
end;
let min = ref Int32.max_int and max = ref Int32.min_int in
let sym = lazy (let s = Symbol.intern sec 0l in
syms := s :: !syms;
s) in
sec.relocs <- filter (reloc sym min max) sec.relocs;
if (sec.sec_opts &&& 0x80000000l = 0l) && !min <= !max then
nonwr := (!min,!max,Lazy.force sym) :: !nonwr
in
List.iter section obj.sections;
int_to_buf data 0;
strsym.value <- Int32.of_int (Buffer.length data);
Buffer.add_buffer data strings;
nonwrsym.value <- Int32.of_int (Buffer.length data);
List.iter
(fun (min,max,secsym) ->
Reloc.abs !machine sect (Int32.of_int (Buffer.length data)) secsym;
int_to_buf data (Int32.to_int min);
Reloc.abs !machine sect (Int32.of_int (Buffer.length data)) secsym;
int_to_buf data (Int32.to_int max);
int_to_buf data 0;
)
!nonwr;
int_to_buf data 0;
int_to_buf data 0;
sect.data <- `String (Buffer.to_bytes data);
obj.sections <- sect :: obj.sections;
obj.symbols <-
(Symbol.export sname sect 0l) ::
strsym :: nonwrsym :: List.filter (fun x -> not (p x)) obj.symbols
@ !syms;
sname
(* Create a table for import symbols __imp_XXX *)
let add_import_table obj imports =
let ptr_size = match !machine with `x86 -> 4 | `x64 -> 8 in
let sect = Section.create ".imptbl" 0xc0300040l in
obj.sections <- sect :: obj.sections;
sect.data <- `String (Bytes.make (ptr_size * List.length imports) '\000');
let i = ref 0 in
List.iter
(fun s ->
let sym = Symbol.extern s in
obj.symbols <-
sym :: Symbol.export ("__imp_" ^ s) sect (Int32.of_int !i) ::
obj.symbols;
Reloc.abs !machine sect (Int32.of_int !i) sym;
i := !i + ptr_size
)
imports
(* Create a table that lists exported symbols (adress,name) *)
let add_export_table obj exports symname =
let sect = Section.create ".exptbl" 0xc0300040l in
let data = Buffer.create 1024 in
let strings = Buffer.create 1024 in
let strsym = Symbol.intern sect 0l in
obj.symbols <- strsym :: (Symbol.export symname sect 0l) :: obj.symbols;
let exports = List.sort Stdlib.compare exports in
(* The runtime library assumes that names are sorted! *)
int_to_buf data (List.length exports);
List.iter
(fun s ->
let sym = Symbol.extern s in
obj.symbols <- sym :: obj.symbols;
Reloc.abs !machine sect (Int32.of_int (Buffer.length data)) sym;
int_to_buf data 0;
Reloc.abs !machine sect (Int32.of_int (Buffer.length data)) strsym;
int_to_buf data (Buffer.length strings);
Buffer.add_string strings (drop_underscore obj s);
Buffer.add_char strings '\000';
)
exports;
strsym.value <- Int32.of_int (Buffer.length data);
let s = Bytes.cat (Buffer.to_bytes data) (Buffer.to_bytes strings) in
sect.data <- `String s;
obj.sections <- sect :: obj.sections
(* A master relocation table points to all the relocation tables
in the DLL *)
let add_master_reloc_table obj names symname =
let sect = Section.create ".mreltbl" 0xc0300040l in
let data = Buffer.create 1024 in
obj.symbols <- (Symbol.export symname sect 0l) :: obj.symbols;
List.iter
(fun s ->
let sym = Symbol.extern s in
obj.symbols <- sym :: obj.symbols;
Reloc.abs !machine sect (Int32.of_int (Buffer.length data)) sym;
int_to_buf data 0;
)
names;
int_to_buf data 0;
sect.data <- `String (Buffer.to_bytes data);
obj.sections <- sect :: obj.sections
let collect_dllexports obj =
let dirs = Coff.directives obj in
let l =
List.map
(function
| (_,x::_) -> x
| _ -> assert false
)
(List.find_all (fun (cmd,_args) -> String.uppercase_ascii cmd = "EXPORT") dirs)
in
match !toolchain with
| `MSVC | `MSVC64 -> List.map (drop_underscore obj) l
| _ -> l
let collect f l =
List.fold_left
(fun accu x -> match f x with None -> accu | Some y -> y :: accu)
[]
l
let cmd_verbose cmd =
debug 1 "+ %s" cmd;
Sys.command cmd
let parse_dll_exports fn =
let ic = open_in fn in
let exps = ref [] in
try
while input_line ic <> "[Ordinal/Name Pointer] Table" do () done;
while true do
let s = input_line ic in
let r = String.index s ']' in
let sym = String.sub s (r+2) (String.length s - r - 2) in
exps := ("_" ^ sym,0) :: !exps;
done;
assert false
with Not_found | End_of_file ->
close_in ic;
!exps
let dll_exports fn = match !toolchain with
| `MSVC | `MSVC64 | `LIGHTLD ->
failwith "Creation of import library not supported for this toolchain"
| `GNAT | `GNAT64 | `CYGWIN64 | `MINGW | `MINGW64 ->
let dmp = temp_file "dyndll" ".dmp" in
if cmd_verbose (Printf.sprintf "%s -p %s > %s" !objdump fn dmp) <> 0
then failwith "Error while extracting exports from a DLL";
parse_dll_exports dmp
let patch_output filename =
match !stack_reserve with
| Some x ->
let filename =
if not (Sys.file_exists filename) && (Sys.file_exists (filename ^ ".exe")) then filename ^ ".exe"
else filename
in
begin try Stacksize.set_stack_reserve filename x
with exn ->
Printf.eprintf "Cannot set stack reserve: %s\n%!"
(Printexc.to_string exn)
end
| None -> ()
(* Extract the set of external symbols required by an object. *)
(* If the object requires "__imp_X", and "X" is available in one of the objects/libraries
(but not "__imp_X" itself), then we consider that "X" is required.
Indeed, we will create "__imp_X" (with a redirection to "X").
Collect such cases in "imported".
*)
let needed imported defined resolve_alias resolve_alternate obj =
let rec normalize name =
try
let r = resolve_alias name in
if r <> name then normalize r else r
with Not_found ->
(* Fall back to alternate name if and only if name was not found.
https://devblogs.microsoft.com/oldnewthing/20200731-00/?p=104024 *)
try
let r = resolve_alternate name in
if r <> name then normalize r else r
with Not_found ->
name
in
let normalize_imp name =
match check_prefix "__imp_" name with
| Some s when not (StrSet.mem name defined) ->
imported := StrSet.add s !imported;
if StrSet.mem s defined then s else name
| None when not (StrSet.mem name defined) && StrSet.mem ("__imp_" ^ name) defined ->
imported := StrSet.add ("__imp_" ^ name) !imported;
"__imp_" ^ name
| _ -> name
in
List.fold_left
(fun accu sym ->
if Symbol.is_extern sym then StrSet.add (normalize_imp (normalize sym.sym_name)) accu
else accu
)
StrSet.empty
obj.symbols
let build_dll link_exe output_file files exts extra_args =
let main_pgm = link_exe <> `DLL in
(* fully resolve filenames, eliminate duplicates *)
let _, files =
List.fold_left
(fun (seen, accu) fn ->
let fn = find_file fn in
let k = String.lowercase_ascii fn in
if StrSet.mem k seen then (seen, accu)
else (StrSet.add k seen, fn :: accu)
) (StrSet.empty, []) files in
let files = List.rev files in
(* load given files *)
let loaded_filenames : (string,unit) Hashtbl.t = Hashtbl.create 16 in
let read_file fn =
if Lib.is_dll fn then `Lib ([], dll_exports fn)
else begin
if !verbose >= 2 then Printf.printf "** open: %s\n" fn;
Lib.read fn
end
in
let files = List.map (fun fn -> fn, read_file fn) files in
List.iter (fun (fn,_) -> Hashtbl.add loaded_filenames fn ()) files;
let objs = collect (function (f, `Obj x) -> Some (f,x) | _ -> None) files in
let libs = collect (function (f, `Lib (x,_)) -> Some (f,x) | _ -> None) files in
let with_data_symbol symbols sym_name f =
if !toolchain <> `MSVC && !toolchain <> `MSVC64 then
match check_prefix "__nm_" sym_name with
| None -> ()
| Some s ->
let imp_name = "__imp_" ^ s in
if List.exists ( fun p -> Symbol.is_defin p &&
p.sym_name = imp_name) symbols then
f s;
in
(* Collect all the available symbols, including those defined
in default libraries *)
let defined, from_imports, resolve_alias, resolve_alternate =
let aliases = Hashtbl.create 16 in
let alternates = Hashtbl.create 16 in
let defined = ref StrSet.empty in
let from_imports = ref StrSet.empty in (* symbols from import libraries *)
let add_def s = defined := StrSet.add s !defined in
let collected = Hashtbl.create 8 in
let rec collect_defined_obj obj =
(* see comments on Cygwin64 COMDATA sections. Here we give a
unique name to the internal symbol. We use ?? to ensure the
symbol is not exported in flexdll export table (see
exportable function) *)
List.iter
(fun sym ->
if has_prefix ".refptr." sym.sym_name then
sym.sym_name <- Printf.sprintf "??flexrefptr%i" (Oo.id (object end))
)
obj.symbols;
(* Collect aliases *)
List.iter
(fun (x, y) ->
debug 2 "alias %s -> %s" x y;
Hashtbl.add aliases x y
)
(Coff.aliases obj);
(* Collect alternatenames *)
let collect_alternatenames alternatenames =
List.iter (fun s -> match String.split_on_char '=' s with
| [alternate_name; true_name] ->
debug 2 "alternatename %s -> %s" alternate_name true_name;
Hashtbl.add alternates alternate_name true_name
| _ ->
debug 1 "alternatenames unrecognized: %s" s;
) alternatenames
in
List.iter (function
| ("alternatename", alternatenames) ->
collect_alternatenames alternatenames
| _ -> ())
(Coff.directives obj);
(* Iterates through DEFAULTLIB directives *)
let register_deflib fn =
if not !custom_crt || not (is_crt_lib fn) then
let fn = find_file fn in
if not (Hashtbl.mem loaded_filenames fn)
then (Hashtbl.add loaded_filenames fn (); collect_file fn)
in
if not !builtin_linker && !use_default_libs then
List.iter
(fun (cmd, args) ->
if String.uppercase_ascii cmd = "DEFAULTLIB" then List.iter register_deflib args
)
(Coff.directives obj);
(* Collect defined symbols *)
List.iter
(fun sym ->
if Symbol.is_defin sym then (
add_def sym.sym_name;
with_data_symbol obj.symbols sym.sym_name add_def)
)
obj.symbols
and collect_file fn =
if not (Hashtbl.mem collected (String.lowercase_ascii fn)) then begin
Hashtbl.replace collected (String.lowercase_ascii fn) ();
debug 2 "** open: %s" fn;
collect_defined fn (Lib.read fn)
end
and collect_defined fn = function
| `Obj obj -> collect_defined_obj obj
| `Lib (objs,imports) ->
List.iter (fun (_, obj) -> collect_defined_obj obj) objs;
List.iter
(fun (s,_) ->
debug 2 "lib %s import symbol %s" fn s;
from_imports := StrSet.add s !from_imports;
add_def s;
add_def ("__imp_" ^ s)
)
imports
in
List.iter
(fun (fn,x) ->
Hashtbl.replace collected (String.lowercase_ascii fn) ();
collect_defined fn x
)
files;
if !use_default_libs then List.iter (fun fn -> collect_file (find_file fn)) !default_libs;
List.iter (fun fn -> collect_file (find_file fn)) exts;
if main_pgm then add_def (usym "static_symtable")
else add_def (usym "reloctbl");
if !machine = `x64 then add_def "__ImageBase"
else add_def "___ImageBase";
!defined, !from_imports, (Hashtbl.find aliases), (Hashtbl.find alternates)
in
(* Determine which objects from the given libraries should be linked
in. First step: find the mapping (symbol -> object) for these
objects. *)
let defined_in =
let defined_in = Hashtbl.create 16 in
let def_in_obj fn (objname, obj) =
List.iter
(fun sym ->
if Symbol.is_defin sym
then begin
let f s =
if !explain then
Printf.printf "Symbol %s found in %s(%s)\n%!" s fn objname;
Hashtbl.replace defined_in s (fn,objname,obj);
in
f sym.sym_name;
with_data_symbol obj.symbols sym.sym_name f
end
)
obj.symbols
in
List.iter
(fun (fn,objs) ->
if !explain then Printf.printf "Scanning lib %s\n%!" fn;
List.iter (def_in_obj fn) objs
)
libs;
Hashtbl.find defined_in
in
let imported_from_implib = ref StrSet.empty in
let imported = ref StrSet.empty in
let imports obj =
let n = needed imported defined resolve_alias resolve_alternate obj in
imported_from_implib := StrSet.union !imported_from_implib (StrSet.inter n from_imports);
let undefs = StrSet.diff n defined in
StrSet.filter
(fun s ->
match check_prefix "__imp_" s with
| Some _ -> false
| None -> s <> "environ" (* special hack for Cygwin64 *)
)
undefs
in
(* Second step: transitive closure, starting from given objects *)
let libobjects = Hashtbl.create 16 in
let reloctbls = ref [] in
let exported = ref StrSet.empty in
List.iter (fun s -> exported := StrSet.add (usym s) !exported) !defexports;
let record_obj obj =
if !builtin_linker then ""
else begin
let fn = temp_file "dyndll" (ext_obj ()) in
let oc = open_out_bin fn in
Coff.put oc obj;
close_out oc;
fn
end
in
let add_reloc name obj imps =
if !show_imports && not (StrSet.is_empty imps) then (
Printf.printf "** Imported symbols for %s:\n%!" name;
StrSet.iter print_endline imps
);
let sym = add_reloc_table obj name (fun s -> StrSet.mem s.sym_name imps) in
reloctbls := sym :: !reloctbls
in
let errors = ref false in
let error_imports name imps =
if main_pgm then begin
Printf.eprintf "** Cannot resolve symbols for %s:\n %s\n%!"
name
(String.concat "\n " (StrSet.elements imps));
errors := true
end
in
let close_obj name imps obj =
error_imports name imps;
add_reloc name obj imps;
record_obj obj
in
let dll_exports = ref StrSet.empty in
let rec link_obj fn obj =
List.iter
(fun sym ->
if Symbol.is_defin sym && exportable sym.sym_name
then exported := StrSet.add sym.sym_name !exported
)
obj.symbols;
dll_exports := List.fold_left (fun accu x -> StrSet.add x accu)
!dll_exports (collect_dllexports obj);
StrSet.iter
(fun s ->
if StrSet.mem s !exported then ()
else
try
let (libname, objname, _) as o = defined_in s in
if !explain then
Printf.printf "%s -> %s(%s) because of %s\n%!" fn libname objname s;
link_libobj o
with Not_found ->
if !explain then
Printf.printf "%s needs %s (not found)\n%!" fn s
)
(needed imported defined resolve_alias resolve_alternate obj)
and link_libobj (libname,objname,obj) =
if Hashtbl.mem libobjects (libname,objname) then ()
else (Hashtbl.replace libobjects (libname,objname) (obj,imports obj);
link_obj (Printf.sprintf "%s(%s)" libname objname) obj)
in
let redirect = Hashtbl.create 16 in
List.iter
(fun (fn, obj) ->
link_obj fn obj;
let imps = imports obj in
if StrSet.is_empty imps then ()
else Hashtbl.replace redirect fn (close_obj fn imps obj);
) objs;
let need_lib = Hashtbl.create 16 in
Hashtbl.iter
(fun (libname,objname) (obj,imps) ->
if StrSet.is_empty imps
then Hashtbl.replace need_lib libname ()
(* the linker will find this object in this library *)
else begin
if !explain then
Printf.printf "Library object %s(%s) needs to be rewritten\n%!"
libname objname;
Hashtbl.add redirect libname
(close_obj (Printf.sprintf "%s(%s)" libname objname) imps obj)
end
)
libobjects;
if !show_exports then (
Printf.printf "** Exported symbols:\n";
StrSet.iter print_endline !exported;
Printf.printf "** Symbols from import libs:\n";
StrSet.iter print_endline !imported_from_implib;
flush stdout
);