bcee6696b68f8da3300a498e1ff89eb393123e8d
[virt-mem.git] / lib / virt_mem.ml
1 (* Memory info for virtual domains.
2    (C) Copyright 2008 Richard W.M. Jones, Red Hat Inc.
3    http://libvirt.org/
4
5    This program is free software; you can redistribute it and/or modify
6    it under the terms of the GNU General Public License as published by
7    the Free Software Foundation; either version 2 of the License, or
8    (at your option) any later version.
9
10    This program is distributed in the hope that it will be useful,
11    but WITHOUT ANY WARRANTY; without even the implied warranty of
12    MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
13    GNU General Public License for more details.
14
15    You should have received a copy of the GNU General Public License
16    along with this program; if not, write to the Free Software
17    Foundation, Inc., 675 Mass Ave, Cambridge, MA 02139, USA.
18  *)
19
20 open Unix
21 open Printf
22 open ExtList
23 open ExtString
24
25 open Virt_mem_gettext.Gettext
26 open Virt_mem_utils
27 module MMap = Virt_mem_mmap
28
29 let min_kallsyms_tabsize = 1_000L
30 let max_kallsyms_tabsize = 250_000L
31
32 type ksym = string
33
34 type image =
35     string
36     * Virt_mem_utils.architecture
37     * ([`Wordsize], [`Endian]) Virt_mem_mmap.t
38     * (ksym -> MMap.addr)
39
40 type kallsyms_compr =
41   | Compressed of (string * MMap.addr) list * MMap.addr
42   | Uncompressed of (string * MMap.addr) list
43
44 let start usage_msg =
45   (* Verbose messages. *)
46   let verbose = ref false in
47
48   (* Default wordsize. *)
49   let def_wordsize = ref None in
50   let set_wordsize = function
51     | "32" -> def_wordsize := Some W32
52     | "64" -> def_wordsize := Some W64
53     | "auto" -> def_wordsize := None
54     | str -> failwith (sprintf (f_"set_wordsize: %s: unknown wordsize") str)
55   in
56
57   (* Default endianness. *)
58   let def_endian = ref None in
59   let set_endian = function
60     | "auto" -> def_endian := None
61     | "le" | "little" | "littleendian" | "intel" ->
62         def_endian := Some Bitmatch.LittleEndian
63     | "be" | "big" | "bigendian" | "motorola" ->
64         def_endian := Some Bitmatch.BigEndian
65     | str -> failwith (sprintf (f_"set_endian: %s: unknown endianness") str)
66   in
67
68   (* Default architecture. *)
69   let def_architecture = ref None in
70   let set_architecture = function
71     | "auto" -> def_architecture := None
72     | arch ->
73         let arch = architecture_of_string arch in
74         def_architecture := Some arch;
75         def_endian := Some (endian_of_architecture arch);
76         def_wordsize := Some (wordsize_of_architecture arch)
77   in
78
79   (* Default text address. *)
80   let def_text_addr = ref 0L (* 0 = auto-detect *) in
81   let set_text_addr = function
82     | "auto" -> def_text_addr := 0L
83     | "i386" -> def_text_addr := 0xc010_0000_L (* common for x86 *)
84     | "x86-64"|"x86_64" -> def_text_addr := 0xffffffff_81000000_L (* x86-64? *)
85     | str -> def_text_addr := Int64.of_string str
86   in
87
88   (* List of kernel images. *)
89   let images = ref [] in
90
91   let memory_image filename =
92     images :=
93       (!def_wordsize, !def_endian, !def_architecture, !def_text_addr, filename)
94     :: !images
95   in
96
97   let argspec = Arg.align [
98     "-A", Arg.String set_architecture,
99     "arch " ^ s_"Set kernel architecture, endianness and word size";
100     "-E", Arg.String set_endian,
101     "endian " ^ s_"Set kernel endianness";
102     "-T", Arg.String set_text_addr,
103     "addr " ^ s_"Set kernel text address";
104     "-W", Arg.String set_wordsize,
105     "addr " ^ s_"Set kernel word size";
106     "-t", Arg.String memory_image,
107     "image " ^ s_"Use saved kernel memory image";
108     "-verbose", Arg.Set verbose,
109     " " ^ s_"Verbose messages";
110   ] in
111
112   let anon_fun str =
113     raise (Arg.Bad (sprintf (f_"%s: unknown parameter") str)) in
114   let usage_msg = usage_msg ^ s_"\n\nOPTIONS" in
115   Arg.parse argspec anon_fun usage_msg;
116
117   let images = !images in
118   let verbose = !verbose in
119
120   (* Get the kernel images. *)
121   let images =
122     if images = [] then
123       (* XXX use libvirt to get images *)
124       failwith "libvirt: not yet implemented"
125     else
126       List.map (
127         fun (wordsize, endian, arch, text_addr, filename) ->
128           (* Quite a lot of limitations on the kernel images we can
129            * handle at the moment ...
130            *)
131           (* XXX We could auto-detect wordsize easily. *)
132           let wordsize =
133             match wordsize with
134             | None ->
135                 failwith
136                   (sprintf (f_"%s: use -W to define word size for this image")
137                      filename);
138             | Some ws -> ws in
139           let endian =
140             match endian with
141             | None ->
142                 failwith
143                   (sprintf (f_"%s: use -E to define endianness for this image")
144                      filename);
145             | Some e -> e in
146
147           let arch =
148             match arch with
149             | Some I386 -> I386 | Some X86_64 -> X86_64
150             | _ ->
151                 failwith
152                   (sprintf (f_"%s: use -A to define architecture (i386/x86-64 only) for this image") filename) in
153
154           if text_addr = 0L then
155             failwith
156               (sprintf (f_"%s: use -T to define kernel load address for this image")
157                  filename);
158
159           (* Map the virtual memory. *)
160           let fd = openfile filename [O_RDONLY] 0 in
161           let mem = MMap.of_file fd text_addr in
162
163           (* Force the wordsize and endianness. *)
164           let mem = MMap.set_wordsize mem wordsize in
165           let mem = MMap.set_endian mem endian in
166
167           (filename, arch, mem)
168       ) images in
169
170   let images =
171     List.map (
172       fun (name, arch, mem) ->
173         (* Look for some common entries in the exported symbol table and
174          * from that find the symbol table itself.  These are just
175          * supposed to be symbols which are very likely to be present
176          * in any Linux kernel, although we only need one of them to be
177          * present to find the symbol table.
178          *
179          * NB. Must not be __initdata, must be in EXPORT_SYMBOL.
180          *)
181         let common_ksyms = [
182           "init_task";                  (* first task_struct *)
183           "root_mountflags";            (* flags for mounting root fs *)
184           "init_uts_ns";                (* uname strings *)
185           "sys_open";                   (* open(2) entry point *)
186           "sys_chdir";                  (* chdir(2) entry point *)
187           "sys_chroot";                 (* chroot(2) entry point *)
188           "sys_umask";                  (* umask(2) entry point *)
189           "schedule";                   (* scheduler entry point *)
190         ] in
191         (* Searching for <NUL>string<NUL> *)
192         let common_ksyms_nul = List.map (sprintf "\000%s\000") common_ksyms in
193
194         (* Search for these strings in the memory image. *)
195         let ksym_strings = List.map (MMap.find_all mem) common_ksyms_nul in
196         let ksym_strings = List.concat ksym_strings in
197         (* Adjust found addresses to start of the string (skip <NUL>). *)
198         let ksym_strings = List.map Int64.succ ksym_strings in
199
200         (* For any we found, try to look up the symbol table
201          * base addr and size.
202          *)
203         let ksymtabs = List.map (
204           fun addr ->
205             (* Search for 'addr' appearing in the image. *)
206             let addrs = MMap.find_pointer_all mem addr in
207
208             (* Now consider each of these addresses and search back
209              * until we reach the beginning of the (possible) symbol
210              * table.
211              *
212              * Kernel symbol table struct is:
213              * struct kernel_symbol {
214              *   unsigned long value;
215              *   const char *name;    <-- initial pointer
216              * } symbols[];
217              *)
218             let pred_long2 addr =
219               MMap.pred_long mem (MMap.pred_long mem addr)
220             in
221             let base_addrs = List.map (
222               fun addr ->
223                 let rec loop addr =
224                   (* '*addr' should point to a C identifier.  If it does,
225                    * step backwards to the previous symbol table entry.
226                    *)
227                   let addrp = MMap.follow_pointer mem addr in
228                   if MMap.is_C_identifier mem addrp then
229                     loop (pred_long2 addr)
230                   else
231                     MMap.succ_long mem addr
232                 in
233                 loop addr
234             ) addrs in
235
236             (* Also look for the end of the symbol table and
237              * calculate its size.
238              *)
239             let base_addrs_sizes = List.map (
240               fun base_addr ->
241                 let rec loop addr =
242                   let addr2 = MMap.succ_long mem addr in
243                   let addr2p = MMap.follow_pointer mem addr2 in
244                   if MMap.is_C_identifier mem addr2p then
245                     loop (MMap.succ_long mem addr2)
246                   else
247                     addr
248                 in
249                 let end_addr = loop base_addr in
250                 base_addr, end_addr -^ base_addr
251             ) base_addrs in
252
253             base_addrs_sizes
254         ) ksym_strings in
255         let ksymtabs = List.concat ksymtabs in
256
257         (* Simply ignore any symbol table candidates which are too small. *)
258         let ksymtabs = List.filter (fun (_, size) -> size > 64L) ksymtabs in
259
260         if verbose then (
261           printf "%s: candidate symbol tables at:\n" name;
262           List.iter (
263             fun (addr, size) ->
264               printf "\t%Lx\t%Lx\t%!" addr size;
265               printf "first symbol: %s\n%!"
266                 (MMap.get_string mem
267                    (MMap.follow_pointer mem
268                       (MMap.succ_long mem addr)))
269           ) ksymtabs
270         );
271
272         (* Vote for the most popular symbol table candidate and from this
273          * generate a function to look up ksyms.
274          *)
275         let lookup_ksym =
276           let freqs = frequency ksymtabs in
277           match freqs with
278           | [] ->
279               eprintf (f_"%s: cannot find start of kernel symbol table\n") name;
280               (fun _ -> raise Not_found)
281
282           | (_, (ksymtab_addr, ksymtab_size)) :: _ ->
283               if verbose then
284                 printf
285                   "%s: Kernel symbol table found at %Lx, size %Lx bytes\n%!"
286                   name ksymtab_addr ksymtab_size;
287
288               (* Load the whole symbol table as a bitstring. *)
289               let ksymtab =
290                 Bitmatch.bitstring_of_string
291                   (MMap.get_bytes mem ksymtab_addr
292                      (Int64.to_int ksymtab_size)) in
293
294               (* Function to look up an address in the symbol table. *)
295               let lookup_ksym sym =
296                 let bits = bits_of_wordsize (MMap.get_wordsize mem) in
297                 let e = MMap.get_endian mem in
298                 let rec loop bs =
299                   bitmatch bs with
300                   | { value : bits : endian(e);
301                       name_ptr : bits : endian(e) }
302                       when MMap.get_string mem name_ptr = sym ->
303                       value
304                   | { _ : bits : endian(e);
305                       _ : bits : endian(e);
306                       bs : -1 : bitstring } ->
307                       loop bs
308                   | { _ } -> raise Not_found
309                 in
310                 loop ksymtab
311               in
312
313               lookup_ksym
314         in
315
316         (* Now try to find the /proc/kallsyms table.  This is in an odd
317          * compressed format (but not a very successful compression
318          * format).  However if it exists we know that it will contain
319          * addresses of the common ksyms above, and it has some
320          * characteristics which make it easy to detect in the
321          * memory.
322          *
323          * kallsyms contains a complete list of symbols so is much
324          * more useful than the basic list of exports.
325          *)
326         let ksym_addrs = List.filter_map (
327           fun ksym -> try Some (lookup_ksym ksym) with Not_found -> None
328         ) common_ksyms in
329
330         (* Search for those kernel addresses in the image.  We're looking
331          * for the table kallsyms_addresses followed by kallsyms_num_syms
332          * (number of symbols in the table).
333          *)
334         let ksym_addrs = List.map (MMap.find_pointer_all mem) ksym_addrs in
335         let ksym_addrs = List.concat ksym_addrs in
336
337         (* Test each one to see if it's a candidate list of kernel
338          * addresses followed by length of list.
339          *)
340         let kallsymtabs = List.filter_map (
341           fun addr ->
342             (* Search upwards from address until we find the length field.
343              * If found, jump backwards by length and check all addresses.
344              *)
345             if verbose then
346               printf "%s: testing candidate kallsyms at %Lx\n" name addr;
347             let rec loop addr =
348               let addrp = MMap.follow_pointer mem addr in
349               if MMap.is_mapped mem addrp then
350                 loop (MMap.succ_long mem addr) (* continue up the table *)
351               else
352                 if addrp >= min_kallsyms_tabsize &&
353                   addrp <= max_kallsyms_tabsize then (
354                   (* addrp might be the symbol count.  Count backwards and
355                    * check the full table.
356                    *)
357                   let num_entries = Int64.to_int addrp in
358                   let entry_size = bytes_of_wordsize (MMap.get_wordsize mem) in
359                   let start_addr =
360                     addr -^ Int64.of_int (entry_size * num_entries) in
361                   let end_addr = addr in
362                   let rec loop2 addr =
363                     if addr < end_addr then (
364                       let addrp = MMap.follow_pointer mem addr in
365                       if MMap.is_mapped mem addrp then
366                         loop2 (MMap.succ_long mem addr)
367                       else
368                         None (* can't verify the full address table *)
369                     ) else
370                       (* ok! *)
371                       let names_addr = MMap.succ_long mem end_addr in
372                       if verbose then
373                         printf "%s: candidate kallsyms found at %Lx (names_addr at %Lx, num_entries %d)\n"
374                           name start_addr names_addr num_entries;
375                       Some (start_addr, num_entries, names_addr)
376                   in
377                   loop2 start_addr
378                 )
379                 else
380                   None (* forget it *)
381             in
382             match loop addr with
383             | None -> None
384             | Some (start_addr, num_entries, names_addr) ->
385                 (* As an additional verification, check the list of
386                  * kallsyms_names.
387                  *)
388                 try
389                   (* If the first byte is '\000' and is followed by a
390                    * C identifier, then this is old-school list of
391                    * symbols with prefix compression as in 2.6.9.
392                    * Otherwise Huffman-compressed kallsyms as in
393                    * 2.6.25.
394                    *)
395                   if MMap.get_byte mem names_addr = 0 &&
396                     MMap.is_C_identifier mem (names_addr+^1L) then (
397                     let names = ref [] in
398                     let prev = ref "" in
399                     let rec loop names_addr start_addr num =
400                       if num > 0 then (
401                         let prefix = MMap.get_byte mem names_addr in
402                         let prefix = String.sub !prev 0 prefix in
403                         let name = MMap.get_string mem (names_addr+^1L) in
404                         let len = String.length name in
405                         let name = prefix ^ name in
406                         prev := name;
407                         let names_addr = names_addr +^ Int64.of_int len +^ 2L in
408                         let sym_value = MMap.follow_pointer mem start_addr in
409                         let start_addr = MMap.succ_long mem start_addr in
410                         (*printf "%S -> %Lx\n" name sym_value;*)
411                         names := (name, sym_value) :: !names;
412                         loop names_addr start_addr (num-1)
413                       )
414                     in
415                     loop names_addr start_addr num_entries;
416                     let names = List.rev !names in
417
418                     Some (start_addr, num_entries, names_addr,
419                           Uncompressed names)
420                     )
421                   else ( (* new-style "compressed" names. *)
422                     let compressed_names = ref [] in
423                     let rec loop names_addr start_addr num =
424                       if num > 0 then (
425                         let len = MMap.get_byte mem names_addr in
426                         let name = MMap.get_bytes mem (names_addr+^1L) len in
427                         let names_addr = names_addr +^ Int64.of_int len +^ 1L in
428                         let sym_value = MMap.follow_pointer mem start_addr in
429                         let start_addr = MMap.succ_long mem start_addr in
430                         compressed_names :=
431                           (name, sym_value) :: !compressed_names;
432                         loop names_addr start_addr (num-1)
433                       ) else
434                         names_addr
435                     in
436                     let markers_addr = loop names_addr start_addr num_entries in
437                     let markers_addr = MMap.align mem markers_addr in
438                     let compressed_names = List.rev !compressed_names in
439
440                     Some (start_addr, num_entries, names_addr,
441                           Compressed (compressed_names, markers_addr))
442                   )
443                 with
444                   Invalid_argument _ -> None (* bad names list *)
445         ) ksym_addrs in
446
447         if verbose then (
448           printf "%s: candidate kallsyms at:\n" name;
449           List.iter (
450             function
451             | (start_addr, num_entries, names_addr, Uncompressed _) ->
452                 printf "\t%Lx %d entries names_addr=%Lx old-style\n%!"
453                   start_addr num_entries names_addr
454             | (start_addr, num_entries, names_addr,
455                Compressed (_, markers_addr)) ->
456                 printf "\t%Lx %d entries names_addr=%Lx markers_addr=%Lx\n%!"
457                   start_addr num_entries names_addr markers_addr
458           ) kallsymtabs
459         );
460
461         (* Vote for the most popular symbol table candidate and
462          * enhance the function for looking up ksyms.
463          *)
464         let lookup_ksym =
465           let freqs = frequency kallsymtabs in
466           match freqs with
467           | [] ->
468               (* Can't find any kallsymtabs, just return the lookup_ksym
469                * function generated previously from the exported symbols.
470                *)
471               lookup_ksym
472
473           | (_, (_, _, _, Uncompressed names)) :: _ ->
474               let lookup_ksym name =
475                 try (* first look it up in kallsyms table. *)
476                   List.assoc name names
477                 with Not_found -> (* try the old exports table instead *)
478                   lookup_ksym name
479               in
480               lookup_ksym
481
482           | (_, (start_addr, num_entries, names_addr,
483                  Compressed (compressed_names, markers_addr))) :: _ ->
484               (* Skip the markers and look for the token table. *)
485               let num_markers = Int64.of_int ((num_entries + 255) / 256) in
486               let marker_size =
487                 Int64.of_int (bytes_of_wordsize (MMap.get_wordsize mem)) in
488               let tokens_addr = markers_addr +^ marker_size *^ num_markers in
489
490               (* Now read out the compression tokens, which are just
491                * 256 ASCIIZ strings that map bytes in the compression
492                * names to substrings.
493                *)
494               let tokens = Array.make 256 "" in
495               let rec loop i addr =
496                 if i < 256 then (
497                   let str = MMap.get_string mem addr in
498                   let len = String.length str in
499                   let addr = addr +^ Int64.of_int (len+1) in
500                   tokens.(i) <- str;
501                   loop (i+1) addr
502                 )
503               in
504               loop 0 tokens_addr;
505
506               (* Expand the compressed names using the tokens. *)
507               let names = List.filter_map (
508                 fun (name, sym_value) ->
509                   let f c = tokens.(Char.code c) in
510                   let name' = String.replace_chars f name in
511                   (*printf "%S -> %S\n" name name';*)
512                   (* First character in uncompressed output is the symbol
513                    * type, eg. 'T'/'t' for text etc.  Since we will never
514                    * be using functions, and since some functions (eg.
515                    * con_start) overlap with data symbols, drop functions.
516                    *)
517                   let typ = name'.[0] in
518                   if typ = 't' || typ = 'T' then None
519                   else (
520                     let name' = String.sub name' 1 (String.length name' - 1) in
521                     Some (name', sym_value)
522                   )
523               ) compressed_names in
524
525               let lookup_ksym name =
526                 try (* first look it up in kallsyms table. *)
527                   List.assoc name names
528                 with Not_found -> (* try the old exports table instead *)
529                   lookup_ksym name
530               in
531
532               lookup_ksym in
533
534         (* Just wrap the lookup_ksym call in something which prints
535          * the query when verbose is set.
536          *)
537         let lookup_ksym =
538           if verbose then
539             let lookup_ksym sym =
540               try
541                 let value = lookup_ksym sym in
542                 printf "lookup_ksym %S = %Lx\n%!" sym value;
543                 value
544               with Not_found ->
545                 printf "lookup_ksym %S failed\n%!" sym;
546                 raise Not_found
547             in
548             lookup_ksym
549           else
550             lookup_ksym
551         in
552
553         ((name, arch, mem, lookup_ksym) : image)
554     ) images in
555
556   verbose, images