1 #include <stdio.h>
2 #include <stdlib.h>
3 #include <string.h>
4 
5 #include "GBA.h"
6 #include "../common/Port.h"
7 #include "elf.h"
8 #include "../NLS.h"
9 
10 #define elfReadMemory(addr) \
11   READ32LE((&map[(addr)>>24].address[(addr) & map[(addr)>>24].mask]))
12 
13 #define DW_TAG_array_type             0x01
14 #define DW_TAG_enumeration_type       0x04
15 #define DW_TAG_formal_parameter       0x05
16 #define DW_TAG_label                  0x0a
17 #define DW_TAG_lexical_block          0x0b
18 #define DW_TAG_member                 0x0d
19 #define DW_TAG_pointer_type           0x0f
20 #define DW_TAG_reference_type         0x10
21 #define DW_TAG_compile_unit           0x11
22 #define DW_TAG_structure_type         0x13
23 #define DW_TAG_subroutine_type        0x15
24 #define DW_TAG_typedef                0x16
25 #define DW_TAG_union_type             0x17
26 #define DW_TAG_unspecified_parameters 0x18
27 #define DW_TAG_inheritance            0x1c
28 #define DW_TAG_inlined_subroutine     0x1d
29 #define DW_TAG_subrange_type          0x21
30 #define DW_TAG_base_type              0x24
31 #define DW_TAG_const_type             0x26
32 #define DW_TAG_enumerator             0x28
33 #define DW_TAG_subprogram             0x2e
34 #define DW_TAG_variable               0x34
35 #define DW_TAG_volatile_type          0x35
36 
37 #define DW_AT_sibling              0x01
38 #define DW_AT_location             0x02
39 #define DW_AT_name                 0x03
40 #define DW_AT_byte_size            0x0b
41 #define DW_AT_bit_offset           0x0c
42 #define DW_AT_bit_size             0x0d
43 #define DW_AT_stmt_list            0x10
44 #define DW_AT_low_pc               0x11
45 #define DW_AT_high_pc              0x12
46 #define DW_AT_language             0x13
47 #define DW_AT_compdir              0x1b
48 #define DW_AT_const_value          0x1c
49 #define DW_AT_containing_type      0x1d
50 #define DW_AT_inline               0x20
51 #define DW_AT_producer             0x25
52 #define DW_AT_prototyped           0x27
53 #define DW_AT_upper_bound          0x2f
54 #define DW_AT_abstract_origin      0x31
55 #define DW_AT_accessibility        0x32
56 #define DW_AT_artificial           0x34
57 #define DW_AT_data_member_location 0x38
58 #define DW_AT_decl_file            0x3a
59 #define DW_AT_decl_line            0x3b
60 #define DW_AT_declaration          0x3c
61 #define DW_AT_encoding             0x3e
62 #define DW_AT_external             0x3f
63 #define DW_AT_frame_base           0x40
64 #define DW_AT_macro_info           0x43
65 #define DW_AT_specification        0x47
66 #define DW_AT_type                 0x49
67 #define DW_AT_virtuality           0x4c
68 #define DW_AT_vtable_elem_location 0x4d
69 // DWARF 2.1/3.0 extensions
70 #define DW_AT_entry_pc             0x52
71 #define DW_AT_ranges               0x55
72 // ARM Compiler extensions
73 #define DW_AT_proc_body            0x2000
74 #define DW_AT_save_offset          0x2001
75 #define DW_AT_user_2002            0x2002
76 // MIPS extensions
77 #define DW_AT_MIPS_linkage_name    0x2007
78 
79 #define DW_FORM_addr      0x01
80 #define DW_FORM_data2     0x05
81 #define DW_FORM_data4     0x06
82 #define DW_FORM_string    0x08
83 #define DW_FORM_block     0x09
84 #define DW_FORM_block1    0x0a
85 #define DW_FORM_data1     0x0b
86 #define DW_FORM_flag      0x0c
87 #define DW_FORM_sdata     0x0d
88 #define DW_FORM_strp      0x0e
89 #define DW_FORM_udata     0x0f
90 #define DW_FORM_ref_addr  0x10
91 #define DW_FORM_ref4      0x13
92 #define DW_FORM_ref_udata 0x15
93 #define DW_FORM_indirect  0x16
94 
95 #define DW_OP_addr        0x03
96 #define DW_OP_plus_uconst 0x23
97 #define DW_OP_reg0        0x50
98 #define DW_OP_reg1        0x51
99 #define DW_OP_reg2        0x52
100 #define DW_OP_reg3        0x53
101 #define DW_OP_reg4        0x54
102 #define DW_OP_reg5        0x55
103 #define DW_OP_reg6        0x56
104 #define DW_OP_reg7        0x57
105 #define DW_OP_reg8        0x58
106 #define DW_OP_reg9        0x59
107 #define DW_OP_reg10       0x5a
108 #define DW_OP_reg11       0x5b
109 #define DW_OP_reg12       0x5c
110 #define DW_OP_reg13       0x5d
111 #define DW_OP_reg14       0x5e
112 #define DW_OP_reg15       0x5f
113 #define DW_OP_fbreg       0x91
114 
115 #define DW_LNS_extended_op      0x00
116 #define DW_LNS_copy             0x01
117 #define DW_LNS_advance_pc       0x02
118 #define DW_LNS_advance_line     0x03
119 #define DW_LNS_set_file         0x04
120 #define DW_LNS_set_column       0x05
121 #define DW_LNS_negate_stmt      0x06
122 #define DW_LNS_set_basic_block  0x07
123 #define DW_LNS_const_add_pc     0x08
124 #define DW_LNS_fixed_advance_pc 0x09
125 
126 #define DW_LNE_end_sequence 0x01
127 #define DW_LNE_set_address  0x02
128 #define DW_LNE_define_file  0x03
129 
130 #define DW_CFA_advance_loc      0x01
131 #define DW_CFA_offset           0x02
132 #define DW_CFA_restore          0x03
133 #define DW_CFA_set_loc          0x01
134 #define DW_CFA_advance_loc1     0x02
135 #define DW_CFA_advance_loc2     0x03
136 #define DW_CFA_advance_loc4     0x04
137 #define DW_CFA_offset_extended  0x05
138 #define DW_CFA_restore_extended 0x06
139 #define DW_CFA_undefined        0x07
140 #define DW_CFA_same_value       0x08
141 #define DW_CFA_register         0x09
142 #define DW_CFA_remember_state   0x0a
143 #define DW_CFA_restore_state    0x0b
144 #define DW_CFA_def_cfa          0x0c
145 #define DW_CFA_def_cfa_register 0x0d
146 #define DW_CFA_def_cfa_offset   0x0e
147 #define DW_CFA_nop              0x00
148 
149 #define CASE_TYPE_TAG \
150     case DW_TAG_const_type:\
151     case DW_TAG_volatile_type:\
152     case DW_TAG_pointer_type:\
153     case DW_TAG_base_type:\
154     case DW_TAG_array_type:\
155     case DW_TAG_structure_type:\
156     case DW_TAG_union_type:\
157     case DW_TAG_typedef:\
158     case DW_TAG_subroutine_type:\
159     case DW_TAG_enumeration_type:\
160     case DW_TAG_enumerator:\
161     case DW_TAG_reference_type
162 
163 struct ELFcie {
164   ELFcie *next;
165   u32 offset;
166   u8 *augmentation;
167   u32 codeAlign;
168   s32 dataAlign;
169   int returnAddress;
170   u8 *data;
171   u32 dataLen;
172 };
173 
174 struct ELFfde {
175   ELFcie *cie;
176   u32 address;
177   u32 end;
178   u8 *data;
179   u32 dataLen;
180 };
181 
182 enum ELFRegMode {
183   REG_NOT_SET,
184   REG_OFFSET,
185   REG_REGISTER
186 };
187 
188 
189 struct ELFFrameStateRegister {
190   ELFRegMode mode;
191   int reg;
192   s32 offset;
193 };
194 
195 struct ELFFrameStateRegisters {
196   ELFFrameStateRegister regs[16];
197   ELFFrameStateRegisters *previous;
198 };
199 
200 enum ELFCfaMode {
201   CFA_NOT_SET,
202   CFA_REG_OFFSET
203 };
204 
205 struct ELFFrameState {
206   ELFFrameStateRegisters registers;
207 
208   ELFCfaMode cfaMode;
209   int cfaRegister;
210   s32 cfaOffset;
211 
212   u32 pc;
213 
214   int dataAlign;
215   int codeAlign;
216   int returnAddress;
217 };
218 
219 extern bool cpuIsMultiBoot;
220 
221 Symbol *elfSymbols = NULL;
222 char *elfSymbolsStrTab = NULL;
223 int elfSymbolsCount = 0;
224 
225 ELFSectionHeader **elfSectionHeaders = NULL;
226 char *elfSectionHeadersStringTable = NULL;
227 int elfSectionHeadersCount = 0;
228 u8 *elfFileData = NULL;
229 
230 CompileUnit *elfCompileUnits = NULL;
231 DebugInfo *elfDebugInfo = NULL;
232 char *elfDebugStrings = NULL;
233 
234 ELFcie *elfCies = NULL;
235 ELFfde **elfFdes = NULL;
236 int elfFdeCount = 0;
237 
238 CompileUnit *elfCurrentUnit = NULL;
239 
240 u32 elfRead4Bytes(u8 *);
241 u16 elfRead2Bytes(u8 *);
242 
elfGetCompileUnit(u32 addr)243 CompileUnit *elfGetCompileUnit(u32 addr)
244 {
245   if(elfCompileUnits) {
246     CompileUnit *unit = elfCompileUnits;
247     while(unit) {
248       if(unit->lowPC) {
249         if(addr >= unit->lowPC && addr < unit->highPC)
250           return unit;
251       } else {
252         ARanges *r = unit->ranges;
253         if(r) {
254           int count = r->count;
255           for(int j = 0; j < count; j++) {
256             if(addr >= r->ranges[j].lowPC && addr < r->ranges[j].highPC)
257               return unit;
258           }
259         }
260       }
261       unit = unit->next;
262     }
263   }
264   return NULL;
265 }
266 
elfGetAddressSymbol(u32 addr)267 const char *elfGetAddressSymbol(u32 addr)
268 {
269   static char buffer[256];
270 
271   CompileUnit *unit = elfGetCompileUnit(addr);
272   // found unit, need to find function
273   if(unit) {
274     Function *func = unit->functions;
275     while(func) {
276       if(addr >= func->lowPC && addr < func->highPC) {
277         int offset = addr - func->lowPC;
278         const char *name = func->name;
279         if(!name)
280           name = "";
281         if(offset)
282           sprintf(buffer, "%s+%d", name, offset);
283         else
284           strcpy(buffer, name);
285         return buffer;
286       }
287       func = func->next;
288     }
289   }
290 
291   if(elfSymbolsCount) {
292     for(int i = 0; i < elfSymbolsCount; i++) {
293       Symbol *s = &elfSymbols[i];
294       if((addr >= s->value)  && addr < (s->value+s->size)) {
295         int offset = addr-s->value;
296         const char *name = s->name;
297         if(name == NULL)
298           name = "";
299         if(offset)
300           sprintf(buffer, "%s+%d", name, addr-s->value);
301         else
302           strcpy(buffer, name);
303         return buffer;
304       } else if(addr == s->value) {
305         if(s->name)
306           strcpy(buffer, s->name);
307         else
308           strcpy(buffer, "");
309         return buffer;
310       }
311     }
312   }
313 
314   return "";
315 }
316 
elfFindLineInModule(u32 * addr,const char * name,int line)317 bool elfFindLineInModule(u32 *addr, const char *name, int line)
318 {
319   CompileUnit *unit = elfCompileUnits;
320 
321   while(unit) {
322     if(unit->lineInfoTable) {
323       int i;
324       int count = unit->lineInfoTable->fileCount;
325       char *found = NULL;
326       for(i = 0; i < count; i++) {
327         if(strcmp(name, unit->lineInfoTable->files[i]) == 0) {
328           found = unit->lineInfoTable->files[i];
329           break;
330         }
331       }
332       // found a matching filename... try to find line now
333       if(found) {
334         LineInfoItem *table = unit->lineInfoTable->lines;
335         count = unit->lineInfoTable->number;
336         for(i = 0; i < count; i++) {
337           if(table[i].file == found && table[i].line == line) {
338             *addr = table[i].address;
339             return true;
340           }
341         }
342         // we can only find a single match
343         return false;
344       }
345     }
346     unit = unit->next;
347   }
348   return false;
349 }
350 
elfFindLine(CompileUnit * unit,Function *,u32 addr,const char ** f)351 int elfFindLine(CompileUnit *unit, Function * /* func */, u32 addr, const char **f)
352 {
353   int currentLine = -1;
354   if(unit->hasLineInfo) {
355     int count = unit->lineInfoTable->number;
356     LineInfoItem *table = unit->lineInfoTable->lines;
357     int i;
358     for(i = 0; i < count; i++) {
359       if(addr <= table[i].address)
360         break;
361     }
362     if(i == count)
363       i--;
364     *f = table[i].file;
365     currentLine = table[i].line;
366   }
367   return currentLine;
368 }
369 
elfFindLineInUnit(u32 * addr,CompileUnit * unit,int line)370 bool elfFindLineInUnit(u32 *addr, CompileUnit *unit, int line)
371 {
372   if(unit->hasLineInfo) {
373     int count = unit->lineInfoTable->number;
374     LineInfoItem *table = unit->lineInfoTable->lines;
375     int i;
376     for(i = 0; i < count; i++) {
377       if(line == table[i].line) {
378         *addr = table[i].address;
379         return true;
380       }
381     }
382   }
383   return false;
384 }
385 
elfGetCurrentFunction(u32 addr,Function ** f,CompileUnit ** u)386 bool elfGetCurrentFunction(u32 addr, Function **f, CompileUnit **u)
387 {
388   CompileUnit *unit = elfGetCompileUnit(addr);
389   // found unit, need to find function
390   if(unit) {
391     Function *func = unit->functions;
392     while(func) {
393       if(addr >= func->lowPC && addr < func->highPC) {
394         *f = func;
395         *u = unit;
396         return true;
397       }
398       func = func->next;
399     }
400   }
401   return false;
402 }
403 
elfGetObject(const char * name,Function * f,CompileUnit * u,Object ** o)404 bool elfGetObject(const char *name, Function *f, CompileUnit *u, Object **o)
405 {
406   if(f && u) {
407     Object *v = f->variables;
408 
409     while(v) {
410       if(strcmp(name, v->name) == 0) {
411         *o = v;
412         return true;
413       }
414       v = v->next;
415     }
416     v = f->parameters;
417     while(v) {
418       if(strcmp(name, v->name) == 0) {
419         *o = v;
420         return true;
421       }
422       v = v->next;
423     }
424     v = u->variables;
425     while(v) {
426       if(strcmp(name, v->name) == 0) {
427         *o = v;
428         return true;
429       }
430       v = v->next;
431     }
432   }
433 
434   CompileUnit *c = elfCompileUnits;
435 
436   while(c) {
437     if(c != u) {
438       Object *v = c->variables;
439       while(v) {
440         if(strcmp(name, v->name) == 0) {
441           *o = v;
442           return true;
443         }
444         v = v->next;
445       }
446     }
447     c = c->next;
448   }
449 
450   return false;
451 }
452 
elfGetSymbol(int i,u32 * value,u32 * size,int * type)453 const char *elfGetSymbol(int i, u32 *value, u32 *size, int *type)
454 {
455   if(i < elfSymbolsCount) {
456     Symbol *s = &elfSymbols[i];
457     *value = s->value;
458     *size = s->size;
459     *type = s->type;
460     return s->name;
461   }
462   return NULL;
463 }
464 
elfGetSymbolAddress(const char * sym,u32 * addr,u32 * size,int * type)465 bool elfGetSymbolAddress(const char *sym, u32 *addr, u32 *size, int *type)
466 {
467   if(elfSymbolsCount) {
468     for(int i = 0; i < elfSymbolsCount; i++) {
469       Symbol *s = &elfSymbols[i];
470       if(strcmp(sym, s->name) == 0) {
471         *addr = s->value;
472         *size = s->size;
473         *type = s->type;
474         return true;
475       }
476     }
477   }
478   return false;
479 }
480 
elfGetFde(u32 address)481 ELFfde *elfGetFde(u32 address)
482 {
483   if(elfFdes) {
484     int i;
485     for(i = 0; i < elfFdeCount; i++) {
486       if(address >= elfFdes[i]->address &&
487          address < elfFdes[i]->end) {
488         return elfFdes[i];
489       }
490     }
491   }
492 
493   return NULL;
494 }
495 
elfExecuteCFAInstructions(ELFFrameState * state,u8 * data,u32 len,u32 pc)496 void elfExecuteCFAInstructions(ELFFrameState *state, u8 *data, u32 len,
497                                u32 pc)
498 {
499   u8 *end = data + len;
500   int bytes;
501   int reg;
502   ELFFrameStateRegisters *fs;
503 
504   while(data < end && state->pc < pc) {
505     u8 op = *data++;
506 
507     switch(op >> 6) {
508     case DW_CFA_advance_loc:
509       state->pc += (op & 0x3f) * state->codeAlign;
510       break;
511     case DW_CFA_offset:
512       reg = op & 0x3f;
513       state->registers.regs[reg].mode = REG_OFFSET;
514       state->registers.regs[reg].offset = state->dataAlign *
515         (s32)elfReadLEB128(data, &bytes);
516       data += bytes;
517       break;
518     case DW_CFA_restore:
519       // we don't care much about the other possible settings,
520       // so just setting to unset is enough for now
521       state->registers.regs[op & 0x3f].mode = REG_NOT_SET;
522       break;
523     case 0:
524       switch(op & 0x3f) {
525       case DW_CFA_nop:
526           break;
527       case DW_CFA_advance_loc1:
528         state->pc += state->codeAlign * (*data++);
529         break;
530       case DW_CFA_advance_loc2:
531         state->pc += state->codeAlign * elfRead2Bytes(data);
532         data += 2;
533         break;
534       case DW_CFA_advance_loc4:
535         state->pc += state->codeAlign * elfRead4Bytes(data);
536         data += 4;
537         break;
538       case DW_CFA_offset_extended:
539         reg = elfReadLEB128(data, &bytes);
540         data += bytes;
541         state->registers.regs[reg].mode = REG_OFFSET;
542         state->registers.regs[reg].offset = state->dataAlign *
543           (s32)elfReadLEB128(data, &bytes);
544         data += bytes;
545         break;
546       case DW_CFA_restore_extended:
547       case DW_CFA_undefined:
548       case DW_CFA_same_value:
549         reg = elfReadLEB128(data, &bytes);
550         data += bytes;
551         state->registers.regs[reg].mode = REG_NOT_SET;
552         break;
553       case DW_CFA_register:
554         reg = elfReadLEB128(data, &bytes);
555         data += bytes;
556         state->registers.regs[reg].mode = REG_REGISTER;
557         state->registers.regs[reg].reg = elfReadLEB128(data, &bytes);
558         data += bytes;
559         break;
560       case DW_CFA_remember_state:
561         fs = (ELFFrameStateRegisters *)calloc(1,
562                                               sizeof(ELFFrameStateRegisters));
563         memcpy(fs, &state->registers, sizeof(ELFFrameStateRegisters));
564         state->registers.previous = fs;
565         break;
566       case DW_CFA_restore_state:
567         if(state->registers.previous == NULL) {
568           printf("Error: previous frame state is NULL.\n");
569           return;
570         }
571         fs = state->registers.previous;
572         memcpy(&state->registers, fs, sizeof(ELFFrameStateRegisters));
573         free(fs);
574         break;
575       case DW_CFA_def_cfa:
576         state->cfaRegister = elfReadLEB128(data, &bytes);
577         data += bytes;
578         state->cfaOffset = (s32)elfReadLEB128(data, &bytes);
579         data += bytes;
580         state->cfaMode = CFA_REG_OFFSET;
581         break;
582       case DW_CFA_def_cfa_register:
583         state->cfaRegister = elfReadLEB128(data, &bytes);
584         data += bytes;
585         state->cfaMode = CFA_REG_OFFSET;
586         break;
587       case DW_CFA_def_cfa_offset:
588         state->cfaOffset = (s32)elfReadLEB128(data, &bytes);
589         data += bytes;
590         state->cfaMode = CFA_REG_OFFSET;
591         break;
592       default:
593         printf("Unknown CFA opcode %08x\n", op);
594         return;
595       }
596       break;
597     default:
598       printf("Unknown CFA opcode %08x\n", op);
599       return;
600     }
601   }
602 }
603 
elfGetFrameState(ELFfde * fde,u32 address)604 ELFFrameState *elfGetFrameState(ELFfde *fde, u32 address)
605 {
606   ELFFrameState *state = (ELFFrameState *)calloc(1, sizeof(ELFFrameState));
607   state->pc = fde->address;
608   state->dataAlign = fde->cie->dataAlign;
609   state->codeAlign = fde->cie->codeAlign;
610   state->returnAddress = fde->cie->returnAddress;
611 
612   elfExecuteCFAInstructions(state,
613                             fde->cie->data,
614                             fde->cie->dataLen,
615                             0xffffffff);
616   elfExecuteCFAInstructions(state,
617                             fde->data,
618                             fde->dataLen,
619                             address);
620 
621   return state;
622 }
623 
elfPrintCallChain(u32 address)624 void elfPrintCallChain(u32 address)
625 {
626   int count = 1;
627 
628   reg_pair regs[15];
629   reg_pair newRegs[15];
630 
631   memcpy(&regs[0], &reg[0], sizeof(reg_pair) * 15);
632 
633   while(count < 20) {
634     const char *addr = elfGetAddressSymbol(address);
635     if(*addr == 0)
636       addr = "???";
637 
638     printf("%08x %s\n", address, addr);
639 
640     ELFfde *fde = elfGetFde(address);
641 
642     if(fde == NULL) {
643       break;
644     }
645 
646     ELFFrameState *state = elfGetFrameState(fde, address);
647 
648     if(!state) {
649       break;
650     }
651 
652     if(state->cfaMode == CFA_REG_OFFSET) {
653       memcpy(&newRegs[0], &regs[0], sizeof(reg_pair) * 15);
654       u32 addr = 0;
655       for(int i = 0; i < 15; i++) {
656         ELFFrameStateRegister *r = &state->registers.
657           regs[i];
658 
659         switch(r->mode) {
660         case REG_NOT_SET:
661           newRegs[i].I = regs[i].I;
662           break;
663         case REG_OFFSET:
664           newRegs[i].I = elfReadMemory(regs[state->cfaRegister].I +
665                                        state->cfaOffset +
666                                        r->offset);
667           break;
668         case REG_REGISTER:
669           newRegs[i].I = regs[r->reg].I;
670           break;
671         default:
672           printf("Unknown register mode: %d\n", r->mode);
673           break;
674         }
675       }
676       memcpy(regs, newRegs, sizeof(reg_pair)*15);
677       addr = newRegs[14].I;
678       addr &= 0xfffffffe;
679       address = addr;
680       count++;
681     } else {
682       printf("CFA not set\n");
683       break;
684     }
685     if(state->registers.previous) {
686       ELFFrameStateRegisters *prev = state->registers.previous;
687 
688       while(prev) {
689         ELFFrameStateRegisters *p = prev->previous;
690         free(prev);
691         prev = p;
692       }
693     }
694     free(state);
695   }
696 }
697 
elfDecodeLocation(Function * f,ELFBlock * o,LocationType * type,u32 base)698 u32 elfDecodeLocation(Function *f, ELFBlock *o, LocationType *type, u32 base)
699 {
700   u32 framebase = 0;
701   if(f && f->frameBase) {
702     ELFBlock *b = f->frameBase;
703     switch(*b->data) {
704     case DW_OP_reg0:
705     case DW_OP_reg1:
706     case DW_OP_reg2:
707     case DW_OP_reg3:
708     case DW_OP_reg4:
709     case DW_OP_reg5:
710     case DW_OP_reg6:
711     case DW_OP_reg7:
712     case DW_OP_reg8:
713     case DW_OP_reg9:
714     case DW_OP_reg10:
715     case DW_OP_reg11:
716     case DW_OP_reg12:
717     case DW_OP_reg13:
718     case DW_OP_reg14:
719     case DW_OP_reg15:
720       framebase = reg[*b->data-0x50].I;
721       break;
722     default:
723       fprintf(stderr, "Unknown frameBase %02x\n", *b->data);
724       break;
725     }
726   }
727 
728   ELFBlock *loc = o;
729   u32 location = 0;
730   int bytes = 0;
731   if(loc) {
732     switch(*loc->data) {
733     case DW_OP_addr:
734       location = elfRead4Bytes(loc->data+1);
735       *type = LOCATION_memory;
736       break;
737     case DW_OP_plus_uconst:
738       location = base + elfReadLEB128(loc->data+1, &bytes);
739       *type = LOCATION_memory;
740       break;
741     case DW_OP_reg0:
742     case DW_OP_reg1:
743     case DW_OP_reg2:
744     case DW_OP_reg3:
745     case DW_OP_reg4:
746     case DW_OP_reg5:
747     case DW_OP_reg6:
748     case DW_OP_reg7:
749     case DW_OP_reg8:
750     case DW_OP_reg9:
751     case DW_OP_reg10:
752     case DW_OP_reg11:
753     case DW_OP_reg12:
754     case DW_OP_reg13:
755     case DW_OP_reg14:
756     case DW_OP_reg15:
757       location = *loc->data - 0x50;
758       *type = LOCATION_register;
759       break;
760     case DW_OP_fbreg:
761       {
762         int bytes;
763         s32 off = elfReadSignedLEB128(loc->data+1, &bytes);
764         location = framebase + off;
765         *type = LOCATION_memory;
766       }
767       break;
768     default:
769       fprintf(stderr, "Unknown location %02x\n", *loc->data);
770       break;
771     }
772   }
773   return location;
774 }
775 
elfDecodeLocation(Function * f,ELFBlock * o,LocationType * type)776 u32 elfDecodeLocation(Function *f, ELFBlock *o, LocationType *type)
777 {
778   return elfDecodeLocation(f, o, type, 0);
779 }
780 
781 // reading function
782 
elfRead4Bytes(u8 * data)783 u32 elfRead4Bytes(u8 *data)
784 {
785   u32 value = *data++;
786   value |= (*data++ << 8);
787   value |= (*data++ << 16);
788   value |= (*data << 24);
789   return value;
790 }
791 
elfRead2Bytes(u8 * data)792 u16 elfRead2Bytes(u8 *data)
793 {
794   u16 value = *data++;
795   value |= (*data << 8);
796   return value;
797 }
798 
elfReadString(u8 * data,int * bytesRead)799 char *elfReadString(u8 *data, int *bytesRead)
800 {
801   if(*data == 0) {
802     *bytesRead = 1;
803     return NULL;
804   }
805   *bytesRead = (int)strlen((char *)data) + 1;
806   return (char *)data;
807 }
808 
elfReadSignedLEB128(u8 * data,int * bytesRead)809 s32 elfReadSignedLEB128(u8 *data, int *bytesRead)
810 {
811   s32 result = 0;
812   int shift = 0;
813   int count = 0;
814 
815   u8 byte;
816   do {
817     byte = *data++;
818     count++;
819     result |= (byte & 0x7f) << shift;
820     shift += 7;
821   } while(byte & 0x80);
822   if((shift < 32) && (byte & 0x40))
823     result |= -(1 << shift);
824   *bytesRead = count;
825   return result;
826 }
827 
elfReadLEB128(u8 * data,int * bytesRead)828 u32 elfReadLEB128(u8 *data, int *bytesRead)
829 {
830   u32 result = 0;
831   int shift = 0;
832   int count = 0;
833   u8 byte;
834   do {
835     byte = *data++;
836     count++;
837     result |= (byte & 0x7f) << shift;
838     shift += 7;
839   } while(byte & 0x80);
840   *bytesRead = count;
841   return result;
842 }
843 
elfReadSection(u8 * data,ELFSectionHeader * sh)844 u8 *elfReadSection(u8 *data, ELFSectionHeader *sh)
845 {
846   return data + READ32LE(&sh->offset);
847 }
848 
elfGetSectionByName(const char * name)849 ELFSectionHeader *elfGetSectionByName(const char *name)
850 {
851   for(int i = 0; i < elfSectionHeadersCount; i++) {
852     if(strcmp(name,
853               &elfSectionHeadersStringTable[READ32LE(&elfSectionHeaders[i]->
854                                                      name)]) == 0) {
855       return elfSectionHeaders[i];
856     }
857   }
858   return NULL;
859 }
860 
elfGetSectionByNumber(int number)861 ELFSectionHeader *elfGetSectionByNumber(int number)
862 {
863   if(number < elfSectionHeadersCount) {
864     return elfSectionHeaders[number];
865   }
866   return NULL;
867 }
868 
elfGetCompileUnitForData(u8 * data)869 CompileUnit *elfGetCompileUnitForData(u8 *data)
870 {
871   u8 *end = elfCurrentUnit->top + 4 + elfCurrentUnit->length;
872 
873   if(data >= elfCurrentUnit->top && data < end)
874     return elfCurrentUnit;
875 
876   CompileUnit *unit = elfCompileUnits;
877 
878   while(unit) {
879     end = unit->top + 4 + unit->length;
880 
881     if(data >= unit->top && data < end)
882       return unit;
883 
884     unit = unit->next;
885   }
886 
887   printf("Error: cannot find reference to compile unit at offset %08x\n",
888          (int)(data - elfDebugInfo->infodata));
889   exit(-1);
890 }
891 
elfReadAttribute(u8 * data,ELFAttr * attr)892 u8 *elfReadAttribute(u8 *data, ELFAttr *attr)
893 {
894   int bytes;
895   int form = attr->form;
896  start:
897   switch(form) {
898   case DW_FORM_addr:
899     attr->value = elfRead4Bytes(data);
900     data += 4;
901     break;
902   case DW_FORM_data2:
903     attr->value = elfRead2Bytes(data);
904     data += 2;
905     break;
906   case DW_FORM_data4:
907     attr->value = elfRead4Bytes(data);
908     data += 4;
909     break;
910   case DW_FORM_string:
911     attr->string = (char *)data;
912     data += strlen(attr->string)+1;
913     break;
914   case DW_FORM_strp:
915     attr->string = elfDebugStrings + elfRead4Bytes(data);
916     data += 4;
917     break;
918   case DW_FORM_block:
919     attr->block = (ELFBlock *)malloc(sizeof(ELFBlock));
920     attr->block->length = elfReadLEB128(data, &bytes);
921     data += bytes;
922     attr->block->data = data;
923     data += attr->block->length;
924     break;
925   case DW_FORM_block1:
926     attr->block = (ELFBlock *)malloc(sizeof(ELFBlock));
927     attr->block->length = *data++;
928     attr->block->data = data;
929     data += attr->block->length;
930     break;
931   case DW_FORM_data1:
932     attr->value = *data++;
933     break;
934   case DW_FORM_flag:
935     attr->flag = (*data++) ? true : false;
936     break;
937   case DW_FORM_sdata:
938     attr->value = elfReadSignedLEB128(data, &bytes);
939     data += bytes;
940     break;
941   case DW_FORM_udata:
942     attr->value = elfReadLEB128(data, &bytes);
943     data += bytes;
944     break;
945   case DW_FORM_ref_addr:
946     attr->value = (u32)((elfDebugInfo->infodata + elfRead4Bytes(data)) - elfGetCompileUnitForData(data)->top);
947     data += 4;
948     break;
949   case DW_FORM_ref4:
950     attr->value = elfRead4Bytes(data);
951     data += 4;
952     break;
953   case DW_FORM_ref_udata:
954     attr->value = (u32)((elfDebugInfo->infodata + (elfGetCompileUnitForData(data)->top - elfDebugInfo->infodata) + elfReadLEB128(data, &bytes)) - elfCurrentUnit->top);
955     data += bytes;
956     break;
957   case DW_FORM_indirect:
958     form = elfReadLEB128(data, &bytes);
959     data += bytes;
960     goto start;
961   default:
962     fprintf(stderr, "Unsupported FORM %02x\n", form);
963     exit(-1);
964   }
965   return data;
966 }
967 
elfGetAbbrev(ELFAbbrev ** table,u32 number)968 ELFAbbrev *elfGetAbbrev(ELFAbbrev **table, u32 number)
969 {
970   int hash = number % 121;
971 
972   ELFAbbrev *abbrev = table[hash];
973 
974   while(abbrev) {
975     if(abbrev->number == number)
976       return abbrev;
977     abbrev = abbrev->next;
978   }
979   return NULL;
980 }
981 
elfReadAbbrevs(u8 * data,u32 offset)982 ELFAbbrev **elfReadAbbrevs(u8 *data, u32 offset)
983 {
984   data += offset;
985   ELFAbbrev **abbrevs = (ELFAbbrev **)calloc(sizeof(ELFAbbrev *)*121,1);
986   int bytes = 0;
987   u32 number = elfReadLEB128(data, &bytes);
988   data += bytes;
989   while(number) {
990     ELFAbbrev *abbrev = (ELFAbbrev *)calloc(sizeof(ELFAbbrev),1);
991 
992     // read tag information
993     abbrev->number = number;
994     abbrev->tag = elfReadLEB128(data, &bytes);
995     data += bytes;
996     abbrev->hasChildren = *data++ ? true: false;
997 
998     // read attributes
999     int name = elfReadLEB128(data, &bytes);
1000     data += bytes;
1001     int form = elfReadLEB128(data, &bytes);
1002     data += bytes;
1003 
1004     while(name) {
1005       if((abbrev->numAttrs % 4) == 0) {
1006         abbrev->attrs = (ELFAttr *)realloc(abbrev->attrs,
1007                                            (abbrev->numAttrs + 4) *
1008                                            sizeof(ELFAttr));
1009       }
1010       abbrev->attrs[abbrev->numAttrs].name = name;
1011       abbrev->attrs[abbrev->numAttrs++].form = form;
1012 
1013       name = elfReadLEB128(data, &bytes);
1014       data += bytes;
1015       form = elfReadLEB128(data, &bytes);
1016       data += bytes;
1017     }
1018 
1019     int hash = number % 121;
1020     abbrev->next = abbrevs[hash];
1021     abbrevs[hash] = abbrev;
1022 
1023     number = elfReadLEB128(data, &bytes);
1024     data += bytes;
1025 
1026     if(elfGetAbbrev(abbrevs, number) != NULL)
1027       break;
1028   }
1029 
1030   return abbrevs;
1031 }
1032 
elfParseCFA(u8 * top)1033 void elfParseCFA(u8 *top)
1034 {
1035   ELFSectionHeader *h = elfGetSectionByName(".debug_frame");
1036 
1037   if(h == NULL) {
1038     return;
1039   }
1040 
1041   u8 *data = elfReadSection(top, h);
1042 
1043   u8 *topOffset = data;
1044 
1045   u8 *end = data + READ32LE(&h->size);
1046 
1047   ELFcie *cies = NULL;
1048 
1049   while(data < end) {
1050     u32 offset = (u32)(data - topOffset);
1051     u32 len = elfRead4Bytes(data);
1052     data += 4;
1053 
1054     u8 *dataEnd = data + len;
1055 
1056     u32 id = elfRead4Bytes(data);
1057     data += 4;
1058 
1059     if(id == 0xffffffff) {
1060       // skip version
1061       (*data)++;
1062 
1063       ELFcie *cie = (ELFcie *)calloc(1, sizeof(ELFcie));
1064 
1065       cie->next = cies;
1066       cies = cie;
1067 
1068       cie->offset = offset;
1069 
1070       cie->augmentation = data;
1071       while(*data)
1072         data++;
1073       data++;
1074 
1075       if(*cie->augmentation) {
1076         fprintf(stderr, "Error: augmentation not supported\n");
1077         exit(-1);
1078       }
1079 
1080       int bytes;
1081       cie->codeAlign = elfReadLEB128(data, &bytes);
1082       data += bytes;
1083 
1084       cie->dataAlign = elfReadSignedLEB128(data, &bytes);
1085       data += bytes;
1086 
1087       cie->returnAddress = *data++;
1088 
1089       cie->data = data;
1090       cie->dataLen = (u32)(dataEnd - data);
1091     } else {
1092       ELFfde *fde = (ELFfde *)calloc(1, sizeof(ELFfde));
1093 
1094       ELFcie *cie = cies;
1095 
1096       while(cie != NULL) {
1097         if(cie->offset == id)
1098           break;
1099         cie = cie->next;
1100       }
1101 
1102       if(!cie) {
1103         fprintf(stderr, "Cannot find CIE %08x\n", id);
1104         exit(-1);
1105       }
1106 
1107       fde->cie = cie;
1108 
1109       fde->address = elfRead4Bytes(data);
1110       data += 4;
1111 
1112       fde->end = fde->address + elfRead4Bytes(data);
1113       data += 4;
1114 
1115       fde->data = data;
1116       fde->dataLen = (u32)(dataEnd - data);
1117 
1118       if((elfFdeCount %10) == 0) {
1119         elfFdes = (ELFfde **)realloc(elfFdes, (elfFdeCount+10) *
1120                                     sizeof(ELFfde *));
1121       }
1122       elfFdes[elfFdeCount++] = fde;
1123     }
1124     data = dataEnd;
1125   }
1126 
1127   elfCies = cies;
1128 }
1129 
elfAddLine(LineInfo * l,u32 a,int file,int line,int * max)1130 void elfAddLine(LineInfo *l, u32 a, int file, int line, int *max)
1131 {
1132   if(l->number == *max) {
1133     *max += 1000;
1134     l->lines = (LineInfoItem *)realloc(l->lines, *max*sizeof(LineInfoItem));
1135   }
1136   LineInfoItem *li = &l->lines[l->number];
1137   li->file = l->files[file-1];
1138   li->address = a;
1139   li->line = line;
1140   l->number++;
1141 }
1142 
elfParseLineInfo(CompileUnit * unit,u8 * top)1143 void elfParseLineInfo(CompileUnit *unit, u8 *top)
1144 {
1145   ELFSectionHeader *h = elfGetSectionByName(".debug_line");
1146   if(h == NULL) {
1147     fprintf(stderr, "No line information found\n");
1148     return;
1149   }
1150   LineInfo *l = unit->lineInfoTable = (LineInfo *)calloc(1, sizeof(LineInfo));
1151   l->number = 0;
1152   int max = 1000;
1153   l->lines = (LineInfoItem *)malloc(1000*sizeof(LineInfoItem));
1154 
1155   u8 *data = elfReadSection(top, h);
1156   data += unit->lineInfo;
1157   u32 totalLen = elfRead4Bytes(data);
1158   data += 4;
1159   u8 *end = data + totalLen;
1160   //  u16 version = elfRead2Bytes(data);
1161   data += 2;
1162   //  u32 offset = elfRead4Bytes(data);
1163   data += 4;
1164   int minInstrSize = *data++;
1165   int defaultIsStmt = *data++;
1166   int lineBase = (s8)*data++;
1167   int lineRange = *data++;
1168   int opcodeBase = *data++;
1169   u8 *stdOpLen = (u8 *)malloc(opcodeBase * sizeof(u8));
1170   stdOpLen[0] = 1;
1171   int i;
1172   for(i = 1; i < opcodeBase; i++)
1173     stdOpLen[i] = *data++;
1174 
1175   free(stdOpLen);// todo
1176   int bytes = 0;
1177 
1178   char *s;
1179   while((s = elfReadString(data, &bytes)) != NULL) {
1180     data += bytes;
1181     //    fprintf(stderr, "Directory is %s\n", s);
1182   }
1183   data += bytes;
1184   int count = 4;
1185   int index = 0;
1186   l->files = (char **)malloc(sizeof(char *)*count);
1187 
1188   while((s = elfReadString(data, &bytes)) != NULL) {
1189     l->files[index++] = s;
1190 
1191     data += bytes;
1192     // directory
1193     elfReadLEB128(data, &bytes);
1194     data += bytes;
1195     // time
1196     elfReadLEB128(data, &bytes);
1197     data += bytes;
1198     // size
1199     elfReadLEB128(data, &bytes);
1200     data += bytes;
1201     //    fprintf(stderr, "File is %s\n", s);
1202     if(index == count) {
1203       count += 4;
1204       l->files = (char **)realloc(l->files, sizeof(char *)*count);
1205     }
1206   }
1207   l->fileCount = index;
1208   data += bytes;
1209 
1210   while(data < end) {
1211     u32 address = 0;
1212     int file = 1;
1213     int line = 1;
1214     int col = 0;
1215     int isStmt = defaultIsStmt;
1216     int basicBlock = 0;
1217     int endSeq = 0;
1218 
1219     while(!endSeq) {
1220       int op = *data++;
1221       switch(op) {
1222       case DW_LNS_extended_op:
1223         {
1224           data++;
1225           op = *data++;
1226           switch(op) {
1227           case DW_LNE_end_sequence:
1228             endSeq = 1;
1229             break;
1230           case DW_LNE_set_address:
1231             address = elfRead4Bytes(data);
1232             data += 4;
1233             break;
1234           default:
1235             fprintf(stderr, "Unknown extended LINE opcode %02x\n", op);
1236             exit(-1);
1237           }
1238         }
1239         break;
1240       case DW_LNS_copy:
1241         //      fprintf(stderr, "Address %08x line %d (%d)\n", address, line, file);
1242         elfAddLine(l, address, file, line, &max);
1243         basicBlock = 0;
1244         break;
1245       case DW_LNS_advance_pc:
1246         address += minInstrSize * elfReadLEB128(data, &bytes);
1247         data += bytes;
1248         break;
1249       case DW_LNS_advance_line:
1250         line += elfReadSignedLEB128(data, &bytes);
1251         data += bytes;
1252         break;
1253       case DW_LNS_set_file:
1254         file = elfReadLEB128(data, &bytes);
1255         data += bytes;
1256         break;
1257       case DW_LNS_set_column:
1258         col = elfReadLEB128(data, &bytes);
1259         data += bytes;
1260         break;
1261       case DW_LNS_negate_stmt:
1262         isStmt = !isStmt;
1263         break;
1264       case DW_LNS_set_basic_block:
1265         basicBlock = 1;
1266         break;
1267       case DW_LNS_const_add_pc:
1268         address += (minInstrSize *((255 - opcodeBase)/lineRange));
1269         break;
1270       case DW_LNS_fixed_advance_pc:
1271         address += elfRead2Bytes(data);
1272         data += 2;
1273         break;
1274       default:
1275         op = op - opcodeBase;
1276         address += (op / lineRange) * minInstrSize;
1277         line += lineBase + (op % lineRange);
1278         elfAddLine(l, address, file, line, &max);
1279         //        fprintf(stderr, "Address %08x line %d (%d)\n", address, line,file);
1280         basicBlock = 1;
1281         break;
1282       }
1283     }
1284   }
1285   l->lines = (LineInfoItem *)realloc(l->lines, l->number*sizeof(LineInfoItem));
1286 }
1287 
elfSkipData(u8 * data,ELFAbbrev * abbrev,ELFAbbrev ** abbrevs)1288 u8 *elfSkipData(u8 *data, ELFAbbrev *abbrev, ELFAbbrev **abbrevs)
1289 {
1290   int i;
1291   int bytes;
1292 
1293   for(i = 0; i < abbrev->numAttrs; i++) {
1294     data = elfReadAttribute(data,  &abbrev->attrs[i]);
1295     if(abbrev->attrs[i].form == DW_FORM_block1)
1296       free(abbrev->attrs[i].block);
1297   }
1298 
1299   if(abbrev->hasChildren) {
1300     int nesting = 1;
1301     while(nesting) {
1302       u32 abbrevNum = elfReadLEB128(data, &bytes);
1303       data += bytes;
1304 
1305       if(!abbrevNum) {
1306         nesting--;
1307         continue;
1308       }
1309 
1310       abbrev = elfGetAbbrev(abbrevs, abbrevNum);
1311 
1312       for(i = 0; i < abbrev->numAttrs; i++) {
1313         data = elfReadAttribute(data,  &abbrev->attrs[i]);
1314         if(abbrev->attrs[i].form == DW_FORM_block1)
1315           free(abbrev->attrs[i].block);
1316       }
1317 
1318       if(abbrev->hasChildren) {
1319         nesting++;
1320       }
1321     }
1322   }
1323   return data;
1324 }
1325 
1326 Type *elfParseType(CompileUnit *unit, u32);
1327 u8 *elfParseObject(u8 *data, ELFAbbrev *abbrev, CompileUnit *unit,
1328                    Object **object);
1329 u8 *elfParseFunction(u8 *data, ELFAbbrev *abbrev, CompileUnit *unit,
1330                      Function **function);
1331 void elfCleanUp(Function *);
1332 
elfAddType(Type * type,CompileUnit * unit,u32 offset)1333 void elfAddType(Type *type, CompileUnit *unit, u32 offset)
1334 {
1335   if(type->next == NULL) {
1336     if(unit->types != type && type->offset == 0) {
1337       type->offset = offset;
1338       type->next = unit->types;
1339       unit->types = type;
1340     }
1341   }
1342 }
1343 
elfParseType(u8 * data,u32 offset,ELFAbbrev * abbrev,CompileUnit * unit,Type ** type)1344 void elfParseType(u8 *data, u32 offset, ELFAbbrev *abbrev, CompileUnit *unit,
1345                   Type **type)
1346 {
1347   switch(abbrev->tag) {
1348   case DW_TAG_typedef:
1349     {
1350       u32 typeref = 0;
1351       char *name = NULL;
1352       for(int i = 0; i < abbrev->numAttrs; i++) {
1353         ELFAttr *attr = &abbrev->attrs[i];
1354         data = elfReadAttribute(data, attr);
1355         switch(attr->name) {
1356         case DW_AT_name:
1357           name = attr->string;
1358           break;
1359         case DW_AT_type:
1360           typeref = attr->value;
1361           break;
1362         case DW_AT_decl_file:
1363         case DW_AT_decl_line:
1364           break;
1365         default:
1366           fprintf(stderr, "Unknown attribute for typedef %02x\n", attr->name);
1367           break;
1368         }
1369       }
1370       if(abbrev->hasChildren)
1371         fprintf(stderr, "Unexpected children for typedef\n");
1372       *type = elfParseType(unit, typeref);
1373       if(name)
1374         (*type)->name = name;
1375       return;
1376     }
1377     break;
1378   case DW_TAG_union_type:
1379   case DW_TAG_structure_type:
1380     {
1381       Type *t = (Type *)calloc(sizeof(Type), 1);
1382       if(abbrev->tag == DW_TAG_structure_type)
1383         t->type = TYPE_struct;
1384       else
1385         t->type = TYPE_union;
1386 
1387       Struct *s = (Struct *)calloc(sizeof(Struct), 1);
1388       t->structure = s;
1389       elfAddType(t, unit, offset);
1390 
1391       for(int i = 0; i < abbrev->numAttrs; i++) {
1392         ELFAttr *attr = &abbrev->attrs[i];
1393         data = elfReadAttribute(data, attr);
1394         switch(attr->name) {
1395         case DW_AT_name:
1396           t->name = attr->string;
1397           break;
1398         case DW_AT_byte_size:
1399           t->size = attr->value;
1400           break;
1401         case DW_AT_decl_file:
1402         case DW_AT_decl_line:
1403         case DW_AT_sibling:
1404         case DW_AT_containing_type: // todo?
1405         case DW_AT_declaration:
1406   case DW_AT_specification: // TODO:
1407           break;
1408         default:
1409           fprintf(stderr, "Unknown attribute for struct %02x\n", attr->name);
1410           break;
1411         }
1412       }
1413       if(abbrev->hasChildren) {
1414         int bytes;
1415         u32 num = elfReadLEB128(data, &bytes);
1416         data += bytes;
1417         int index = 0;
1418         while(num) {
1419           ELFAbbrev *abbr = elfGetAbbrev(unit->abbrevs, num);
1420 
1421           switch(abbr->tag) {
1422           case DW_TAG_member:
1423             {
1424               if((index % 4) == 0)
1425                 s->members = (Member *)realloc(s->members,
1426                                                sizeof(Member)*(index+4));
1427               Member *m = &s->members[index];
1428               m->location = NULL;
1429               m->bitOffset = 0;
1430               m->bitSize = 0;
1431               m->byteSize = 0;
1432               for(int i = 0; i < abbr->numAttrs; i++) {
1433                 ELFAttr *attr = &abbr->attrs[i];
1434                 data = elfReadAttribute(data, attr);
1435                 switch(attr->name) {
1436                 case DW_AT_name:
1437                   m->name = attr->string;
1438                   break;
1439                 case DW_AT_type:
1440                   m->type = elfParseType(unit, attr->value);
1441                   break;
1442                 case DW_AT_data_member_location:
1443                   m->location = attr->block;
1444                   break;
1445                 case DW_AT_byte_size:
1446                   m->byteSize = attr->value;
1447                   break;
1448                 case DW_AT_bit_offset:
1449                   m->bitOffset = attr->value;
1450                   break;
1451                 case DW_AT_bit_size:
1452                   m->bitSize = attr->value;
1453                   break;
1454                 case DW_AT_decl_file:
1455                 case DW_AT_decl_line:
1456                 case DW_AT_accessibility:
1457                 case DW_AT_artificial: // todo?
1458                   break;
1459                 default:
1460                   fprintf(stderr, "Unknown member attribute %02x\n",
1461                           attr->name);
1462                 }
1463               }
1464               index++;
1465             }
1466             break;
1467           case DW_TAG_subprogram:
1468             {
1469               Function *fnc = NULL;
1470               data = elfParseFunction(data, abbr, unit, &fnc);
1471               if(fnc != NULL) {
1472                 if(unit->lastFunction)
1473                   unit->lastFunction->next = fnc;
1474                 else
1475                   unit->functions = fnc;
1476                 unit->lastFunction = fnc;
1477               }
1478             }
1479             break;
1480           case DW_TAG_inheritance:
1481             // TODO: add support
1482             data = elfSkipData(data, abbr, unit->abbrevs);
1483             break;
1484           CASE_TYPE_TAG:
1485             // skip types... parsed only when used
1486             data = elfSkipData(data, abbr, unit->abbrevs);
1487             break;
1488           case DW_TAG_variable:
1489             data = elfSkipData(data, abbr, unit->abbrevs);
1490             break;
1491           default:
1492             fprintf(stderr, "Unknown struct tag %02x %s\n", abbr->tag, t->name);
1493             data = elfSkipData(data, abbr, unit->abbrevs);
1494             break;
1495           }
1496           num = elfReadLEB128(data, &bytes);
1497           data += bytes;
1498         }
1499         s->memberCount = index;
1500       }
1501       *type = t;
1502       return;
1503     }
1504     break;
1505   case DW_TAG_base_type:
1506     {
1507       Type *t = (Type *)calloc(sizeof(Type), 1);
1508 
1509       t->type = TYPE_base;
1510       elfAddType(t, unit, offset);
1511       for(int i = 0; i < abbrev->numAttrs; i++) {
1512         ELFAttr *attr = &abbrev->attrs[i];
1513         data = elfReadAttribute(data, attr);
1514         switch(attr->name) {
1515         case DW_AT_name:
1516           t->name = attr->string;
1517           break;
1518         case DW_AT_encoding:
1519           t->encoding = attr->value;
1520           break;
1521         case DW_AT_byte_size:
1522           t->size = attr->value;
1523           break;
1524         case DW_AT_bit_size:
1525           t->bitSize = attr->value;
1526           break;
1527         default:
1528           fprintf(stderr, "Unknown attribute for base type %02x\n",
1529                   attr->name);
1530           break;
1531         }
1532       }
1533       if(abbrev->hasChildren)
1534         fprintf(stderr, "Unexpected children for base type\n");
1535       *type = t;
1536       return;
1537     }
1538     break;
1539   case DW_TAG_pointer_type:
1540     {
1541       Type *t = (Type *)calloc(sizeof(Type), 1);
1542 
1543       t->type = TYPE_pointer;
1544 
1545       elfAddType(t, unit, offset);
1546 
1547       for(int i = 0; i < abbrev->numAttrs; i++) {
1548         ELFAttr *attr = &abbrev->attrs[i];
1549         data =elfReadAttribute(data, attr);
1550         switch(attr->name) {
1551         case DW_AT_type:
1552           t->pointer = elfParseType(unit, attr->value);
1553           break;
1554         case DW_AT_byte_size:
1555           t->size = attr->value;
1556           break;
1557         default:
1558           fprintf(stderr, "Unknown pointer type attribute %02x\n", attr->name);
1559           break;
1560         }
1561       }
1562       if(abbrev->hasChildren)
1563         fprintf(stderr, "Unexpected children for pointer type\n");
1564       *type = t;
1565       return;
1566     }
1567     break;
1568   case DW_TAG_reference_type:
1569     {
1570       Type *t = (Type *)calloc(sizeof(Type), 1);
1571 
1572       t->type = TYPE_reference;
1573 
1574       elfAddType(t, unit, offset);
1575 
1576       for(int i = 0; i < abbrev->numAttrs; i++) {
1577         ELFAttr *attr = &abbrev->attrs[i];
1578         data =elfReadAttribute(data, attr);
1579         switch(attr->name) {
1580         case DW_AT_type:
1581           t->pointer = elfParseType(unit, attr->value);
1582           break;
1583         case DW_AT_byte_size:
1584           t->size = attr->value;
1585           break;
1586         default:
1587           fprintf(stderr, "Unknown ref type attribute %02x\n", attr->name);
1588           break;
1589         }
1590       }
1591       if(abbrev->hasChildren)
1592         fprintf(stderr, "Unexpected children for ref type\n");
1593       *type = t;
1594       return;
1595     }
1596     break;
1597   case DW_TAG_volatile_type:
1598     {
1599       u32 typeref = 0;
1600 
1601       for(int i = 0; i < abbrev->numAttrs; i++) {
1602         ELFAttr *attr = &abbrev->attrs[i];
1603         data = elfReadAttribute(data, attr);
1604         switch(attr->name) {
1605         case DW_AT_type:
1606           typeref = attr->value;
1607           break;
1608         default:
1609           fprintf(stderr, "Unknown volatile attribute for type %02x\n",
1610                   attr->name);
1611           break;
1612         }
1613       }
1614       if(abbrev->hasChildren)
1615         fprintf(stderr, "Unexpected children for volatile type\n");
1616       *type = elfParseType(unit, typeref);
1617       return;
1618     }
1619     break;
1620   case DW_TAG_const_type:
1621     {
1622       u32 typeref = 0;
1623 
1624       for(int i = 0; i < abbrev->numAttrs; i++) {
1625         ELFAttr *attr = &abbrev->attrs[i];
1626         data = elfReadAttribute(data, attr);
1627         switch(attr->name) {
1628         case DW_AT_type:
1629           typeref = attr->value;
1630           break;
1631         default:
1632           fprintf(stderr, "Unknown const attribute for type %02x\n",
1633                   attr->name);
1634           break;
1635         }
1636       }
1637       if(abbrev->hasChildren)
1638         fprintf(stderr, "Unexpected children for const type\n");
1639       *type = elfParseType(unit, typeref);
1640       return;
1641     }
1642     break;
1643   case DW_TAG_enumeration_type:
1644     {
1645       Type *t = (Type *)calloc(sizeof(Type), 1);
1646       t->type = TYPE_enum;
1647       Enum *e = (Enum *)calloc(sizeof(Enum), 1);
1648       t->enumeration = e;
1649       elfAddType(t, unit, offset);
1650       int count = 0;
1651       for(int i = 0; i < abbrev->numAttrs; i++) {
1652         ELFAttr *attr = &abbrev->attrs[i];
1653         data = elfReadAttribute(data, attr);
1654         switch(attr->name) {
1655         case DW_AT_name:
1656           t->name = attr->string;
1657           break;
1658         case DW_AT_byte_size:
1659           t->size = attr->value;
1660           break;
1661         case DW_AT_sibling:
1662         case DW_AT_decl_file:
1663         case DW_AT_decl_line:
1664           break;
1665         default:
1666           fprintf(stderr, "Unknown enum attribute %02x\n", attr->name);
1667         }
1668       }
1669       if(abbrev->hasChildren) {
1670         int bytes;
1671         u32 num = elfReadLEB128(data, &bytes);
1672         data += bytes;
1673         while(num) {
1674           ELFAbbrev *abbr = elfGetAbbrev(unit->abbrevs, num);
1675 
1676           switch(abbr->tag) {
1677           case DW_TAG_enumerator:
1678             {
1679               count++;
1680               e->members = (EnumMember *)realloc(e->members,
1681                                                  count*sizeof(EnumMember));
1682               EnumMember *m = &e->members[count-1];
1683               for(int i = 0; i < abbr->numAttrs; i++) {
1684                 ELFAttr *attr = &abbr->attrs[i];
1685                 data = elfReadAttribute(data, attr);
1686                 switch(attr->name) {
1687                 case DW_AT_name:
1688                   m->name = attr->string;
1689                   break;
1690                 case DW_AT_const_value:
1691                   m->value = attr->value;
1692                   break;
1693                 default:
1694                   fprintf(stderr, "Unknown sub param attribute %02x\n",
1695                           attr->name);
1696                 }
1697               }
1698             }
1699             break;
1700           default:
1701             fprintf(stderr, "Unknown enum tag %02x\n", abbr->tag);
1702             data = elfSkipData(data, abbr, unit->abbrevs);
1703             break;
1704           }
1705           num = elfReadLEB128(data, &bytes);
1706           data += bytes;
1707         }
1708       }
1709       e->count = count;
1710       *type = t;
1711       return;
1712     }
1713     break;
1714   case DW_TAG_subroutine_type:
1715     {
1716       Type *t = (Type *)calloc(sizeof(Type), 1);
1717       t->type = TYPE_function;
1718       FunctionType *f = (FunctionType *)calloc(sizeof(FunctionType), 1);
1719       t->function = f;
1720       elfAddType(t, unit, offset);
1721       for(int i = 0; i < abbrev->numAttrs; i++) {
1722         ELFAttr *attr = &abbrev->attrs[i];
1723         data = elfReadAttribute(data, attr);
1724         switch(attr->name) {
1725         case DW_AT_prototyped:
1726         case DW_AT_sibling:
1727           break;
1728         case DW_AT_type:
1729           f->returnType = elfParseType(unit, attr->value);
1730           break;
1731         default:
1732           fprintf(stderr, "Unknown subroutine attribute %02x\n", attr->name);
1733         }
1734       }
1735       if(abbrev->hasChildren) {
1736         int bytes;
1737         u32 num = elfReadLEB128(data, &bytes);
1738         data += bytes;
1739         Object *lastVar = NULL;
1740         while(num) {
1741           ELFAbbrev *abbr = elfGetAbbrev(unit->abbrevs, num);
1742 
1743           switch(abbr->tag) {
1744           case DW_TAG_formal_parameter:
1745             {
1746               Object *o;
1747               data = elfParseObject(data, abbr, unit, &o);
1748               if(f->args)
1749                 lastVar->next = o;
1750               else
1751                 f->args = o;
1752               lastVar = o;
1753             }
1754             break;
1755           case DW_TAG_unspecified_parameters:
1756             // no use in the debugger yet
1757             data = elfSkipData(data, abbr, unit->abbrevs);
1758             break;
1759           CASE_TYPE_TAG:
1760             // skip types... parsed only when used
1761             data = elfSkipData(data, abbr, unit->abbrevs);
1762             break;
1763           default:
1764             fprintf(stderr, "Unknown subroutine tag %02x\n", abbr->tag);
1765             data = elfSkipData(data, abbr, unit->abbrevs);
1766             break;
1767           }
1768           num = elfReadLEB128(data, &bytes);
1769           data += bytes;
1770         }
1771       }
1772       *type = t;
1773       return;
1774     }
1775     break;
1776   case DW_TAG_array_type:
1777     {
1778       u32 typeref = 0;
1779       int i;
1780       Array *array = (Array *)calloc(sizeof(Array), 1);
1781       Type *t = (Type *)calloc(sizeof(Type), 1);
1782       t->type = TYPE_array;
1783       elfAddType(t, unit, offset);
1784 
1785       for(i = 0; i < abbrev->numAttrs; i++) {
1786         ELFAttr *attr = &abbrev->attrs[i];
1787         data = elfReadAttribute(data, attr);
1788         switch(attr->name) {
1789         case DW_AT_sibling:
1790           break;
1791         case DW_AT_type:
1792           typeref = attr->value;
1793           array->type = elfParseType(unit, typeref);
1794           break;
1795         default:
1796           fprintf(stderr, "Unknown array attribute %02x\n", attr->name);
1797         }
1798       }
1799       if(abbrev->hasChildren) {
1800         int bytes;
1801         u32 num = elfReadLEB128(data, &bytes);
1802         data += bytes;
1803         int index = 0;
1804         int maxBounds = 0;
1805         while(num) {
1806           ELFAbbrev *abbr = elfGetAbbrev(unit->abbrevs, num);
1807 
1808           switch(abbr->tag) {
1809           case DW_TAG_subrange_type:
1810             {
1811               if(maxBounds == index) {
1812                 maxBounds += 4;
1813                 array->bounds = (int *)realloc(array->bounds,
1814                                                sizeof(int)*maxBounds);
1815               }
1816               for(int i = 0; i < abbr->numAttrs; i++) {
1817                 ELFAttr *attr = &abbr->attrs[i];
1818                 data = elfReadAttribute(data, attr);
1819                 switch(attr->name) {
1820                 case DW_AT_upper_bound:
1821                   array->bounds[index] = attr->value+1;
1822                   break;
1823                 case DW_AT_type: // ignore
1824                   break;
1825                 default:
1826                   fprintf(stderr, "Unknown subrange attribute %02x\n",
1827                           attr->name);
1828                 }
1829               }
1830               index++;
1831             }
1832             break;
1833           default:
1834             fprintf(stderr, "Unknown array tag %02x\n", abbr->tag);
1835             data = elfSkipData(data, abbr, unit->abbrevs);
1836             break;
1837           }
1838           num = elfReadLEB128(data, &bytes);
1839           data += bytes;
1840         }
1841         array->maxBounds = index;
1842       }
1843       t->size = array->type->size;
1844       for(i = 0; i < array->maxBounds; i++)
1845         t->size *= array->bounds[i];
1846       t->array = array;
1847       *type = t;
1848       return;
1849     }
1850     break;
1851   default:
1852     fprintf(stderr, "Unknown type TAG %02x\n", abbrev->tag);
1853     exit(-1);
1854   }
1855 }
1856 
elfParseType(CompileUnit * unit,u32 offset)1857 Type *elfParseType(CompileUnit *unit, u32 offset)
1858 {
1859   Type *t = unit->types;
1860 
1861   while(t) {
1862     if(t->offset == offset)
1863       return t;
1864     t = t->next;
1865   }
1866   if(offset == 0) {
1867     Type *t = (Type *)calloc(sizeof(Type), 1);
1868     t->type = TYPE_void;
1869     t->offset = 0;
1870     elfAddType(t, unit, 0);
1871     return t;
1872   }
1873   u8 *data = unit->top + offset;
1874   int bytes;
1875   int abbrevNum = elfReadLEB128(data, &bytes);
1876   data += bytes;
1877   Type *type = NULL;
1878 
1879   ELFAbbrev *abbrev = elfGetAbbrev(unit->abbrevs, abbrevNum);
1880 
1881   elfParseType(data, offset, abbrev, unit, &type);
1882   return type;
1883 }
1884 
elfGetObjectAttributes(CompileUnit * unit,u32 offset,Object * o)1885 void elfGetObjectAttributes(CompileUnit *unit, u32 offset, Object *o)
1886 {
1887   u8 *data = unit->top + offset;
1888   int bytes;
1889   u32 abbrevNum = elfReadLEB128(data, &bytes);
1890   data += bytes;
1891 
1892   if(!abbrevNum) {
1893     return;
1894   }
1895 
1896   ELFAbbrev *abbrev = elfGetAbbrev(unit->abbrevs, abbrevNum);
1897 
1898   for(int i = 0; i < abbrev->numAttrs; i++) {
1899     ELFAttr *attr = &abbrev->attrs[i];
1900     data = elfReadAttribute(data, attr);
1901     switch(attr->name) {
1902     case DW_AT_location:
1903       o->location = attr->block;
1904       break;
1905     case DW_AT_name:
1906       if(o->name == NULL)
1907         o->name = attr->string;
1908       break;
1909     case DW_AT_MIPS_linkage_name:
1910       o->name = attr->string;
1911       break;
1912     case DW_AT_decl_file:
1913       o->file = attr->value;
1914       break;
1915     case DW_AT_decl_line:
1916       o->line = attr->value;
1917       break;
1918     case DW_AT_type:
1919       o->type = elfParseType(unit, attr->value);
1920       break;
1921     case DW_AT_external:
1922       o->external = attr->flag;
1923       break;
1924     case DW_AT_const_value:
1925     case DW_AT_abstract_origin:
1926     case DW_AT_declaration:
1927     case DW_AT_artificial:
1928       // todo
1929       break;
1930     case DW_AT_specification:
1931       // TODO:
1932       break;
1933     default:
1934       fprintf(stderr, "Unknown object attribute %02x\n", attr->name);
1935       break;
1936     }
1937   }
1938 }
1939 
elfParseObject(u8 * data,ELFAbbrev * abbrev,CompileUnit * unit,Object ** object)1940 u8 *elfParseObject(u8 *data, ELFAbbrev *abbrev, CompileUnit *unit,
1941                    Object **object)
1942 {
1943   Object *o = (Object *)calloc(sizeof(Object), 1);
1944 
1945   o->next = NULL;
1946 
1947   for(int i = 0; i < abbrev->numAttrs; i++) {
1948     ELFAttr *attr = &abbrev->attrs[i];
1949     data = elfReadAttribute(data, attr);
1950     switch(attr->name) {
1951     case DW_AT_location:
1952       o->location = attr->block;
1953       break;
1954     case DW_AT_name:
1955       if(o->name == NULL)
1956         o->name = attr->string;
1957       break;
1958     case DW_AT_MIPS_linkage_name:
1959       o->name = attr->string;
1960       break;
1961     case DW_AT_decl_file:
1962       o->file = attr->value;
1963       break;
1964     case DW_AT_decl_line:
1965       o->line = attr->value;
1966       break;
1967     case DW_AT_type:
1968       o->type = elfParseType(unit, attr->value);
1969       break;
1970     case DW_AT_external:
1971       o->external = attr->flag;
1972       break;
1973     case DW_AT_abstract_origin:
1974       elfGetObjectAttributes(unit, attr->value, o);
1975       break;
1976     case DW_AT_const_value:
1977     case DW_AT_declaration:
1978     case DW_AT_artificial:
1979       break;
1980     case DW_AT_specification:
1981       // TODO:
1982       break;
1983     default:
1984       fprintf(stderr, "Unknown object attribute %02x\n", attr->name);
1985       break;
1986     }
1987   }
1988   *object = o;
1989   return data;
1990 }
1991 
elfParseBlock(u8 * data,ELFAbbrev * abbrev,CompileUnit * unit,Function * func,Object ** lastVar)1992 u8 *elfParseBlock(u8 *data, ELFAbbrev *abbrev, CompileUnit *unit,
1993                   Function *func, Object **lastVar)
1994 {
1995   int bytes;
1996   u32 start = func->lowPC;
1997   u32 end = func->highPC;
1998 
1999   for(int i = 0; i < abbrev->numAttrs; i++) {
2000     ELFAttr *attr = &abbrev->attrs[i];
2001     data = elfReadAttribute(data, attr);
2002     switch(attr->name) {
2003     case DW_AT_sibling:
2004       break;
2005     case DW_AT_low_pc:
2006       start = attr->value;
2007       break;
2008     case DW_AT_high_pc:
2009       end = attr->value;
2010       break;
2011     case DW_AT_ranges: // ignore for now
2012       break;
2013     default:
2014       fprintf(stderr, "Unknown block attribute %02x\n", attr->name);
2015       break;
2016     }
2017   }
2018 
2019   if(abbrev->hasChildren) {
2020     int nesting = 1;
2021 
2022     while(nesting) {
2023       u32 abbrevNum = elfReadLEB128(data, &bytes);
2024       data += bytes;
2025 
2026       if(!abbrevNum) {
2027         nesting--;
2028         continue;
2029       }
2030 
2031       abbrev = elfGetAbbrev(unit->abbrevs, abbrevNum);
2032 
2033       switch(abbrev->tag) {
2034       CASE_TYPE_TAG: // types only parsed when used
2035       case DW_TAG_label: // not needed
2036         data = elfSkipData(data, abbrev, unit->abbrevs);
2037         break;
2038       case DW_TAG_lexical_block:
2039         data = elfParseBlock(data, abbrev, unit, func, lastVar);
2040         break;
2041       case DW_TAG_subprogram:
2042         {
2043           Function *f = NULL;
2044           data = elfParseFunction(data, abbrev, unit, &f);
2045           if(f != NULL) {
2046             if(unit->lastFunction)
2047               unit->lastFunction->next = f;
2048             else
2049               unit->functions = f;
2050             unit->lastFunction = f;
2051           }
2052         }
2053         break;
2054       case DW_TAG_variable:
2055         {
2056           Object *o;
2057           data = elfParseObject(data, abbrev, unit, &o);
2058           if(o->startScope == 0)
2059             o->startScope = start;
2060           if(o->endScope == 0)
2061             o->endScope = 0;
2062           if(func->variables)
2063             (*lastVar)->next = o;
2064           else
2065             func->variables = o;
2066           *lastVar = o;
2067         }
2068         break;
2069       case DW_TAG_inlined_subroutine:
2070         // TODO:
2071         data = elfSkipData(data, abbrev, unit->abbrevs);
2072         break;
2073       default:
2074         {
2075           fprintf(stderr, "Unknown block TAG %02x\n", abbrev->tag);
2076           data = elfSkipData(data, abbrev, unit->abbrevs);
2077         }
2078         break;
2079       }
2080     }
2081   }
2082   return data;
2083 }
2084 
elfGetFunctionAttributes(CompileUnit * unit,u32 offset,Function * func)2085 void elfGetFunctionAttributes(CompileUnit *unit, u32 offset, Function *func)
2086 {
2087   u8 *data = unit->top + offset;
2088   int bytes;
2089   u32 abbrevNum = elfReadLEB128(data, &bytes);
2090   data += bytes;
2091 
2092   if(!abbrevNum) {
2093     return;
2094   }
2095 
2096   ELFAbbrev *abbrev = elfGetAbbrev(unit->abbrevs, abbrevNum);
2097 
2098   for(int i = 0; i < abbrev->numAttrs; i++) {
2099     ELFAttr *attr = &abbrev->attrs[i];
2100     data = elfReadAttribute(data, attr);
2101 
2102     switch(attr->name) {
2103     case DW_AT_sibling:
2104       break;
2105     case DW_AT_name:
2106       if(func->name == NULL)
2107         func->name = attr->string;
2108       break;
2109     case DW_AT_MIPS_linkage_name:
2110       func->name = attr->string;
2111       break;
2112     case DW_AT_low_pc:
2113       func->lowPC = attr->value;
2114       break;
2115     case DW_AT_high_pc:
2116       func->highPC = attr->value;
2117       break;
2118     case DW_AT_decl_file:
2119       func->file = attr->value;
2120       break;
2121     case DW_AT_decl_line:
2122       func->line = attr->value;
2123       break;
2124     case DW_AT_external:
2125       func->external = attr->flag;
2126       break;
2127     case DW_AT_frame_base:
2128       func->frameBase = attr->block;
2129       break;
2130     case DW_AT_type:
2131       func->returnType = elfParseType(unit, attr->value);
2132       break;
2133     case DW_AT_inline:
2134     case DW_AT_specification:
2135     case DW_AT_declaration:
2136     case DW_AT_artificial:
2137     case DW_AT_prototyped:
2138     case DW_AT_proc_body:
2139     case DW_AT_save_offset:
2140     case DW_AT_user_2002:
2141     case DW_AT_virtuality:
2142     case DW_AT_containing_type:
2143     case DW_AT_accessibility:
2144       // todo;
2145       break;
2146     case DW_AT_vtable_elem_location:
2147       free(attr->block);
2148       break;
2149     default:
2150       fprintf(stderr, "Unknown function attribute %02x\n", attr->name);
2151       break;
2152     }
2153   }
2154 
2155   return;
2156 }
2157 
elfParseFunction(u8 * data,ELFAbbrev * abbrev,CompileUnit * unit,Function ** f)2158 u8 *elfParseFunction(u8 *data, ELFAbbrev *abbrev, CompileUnit *unit,
2159                      Function **f)
2160 {
2161   Function *func = (Function *)calloc(sizeof(Function), 1);
2162   *f = func;
2163 
2164   int bytes;
2165   bool mangled = false;
2166   bool declaration = false;
2167   for(int i = 0; i < abbrev->numAttrs; i++) {
2168     ELFAttr *attr = &abbrev->attrs[i];
2169     data = elfReadAttribute(data, attr);
2170     switch(attr->name) {
2171     case DW_AT_sibling:
2172       break;
2173     case DW_AT_name:
2174       if(func->name == NULL)
2175         func->name = attr->string;
2176       break;
2177     case DW_AT_MIPS_linkage_name:
2178       func->name = attr->string;
2179       mangled = true;
2180       break;
2181     case DW_AT_low_pc:
2182       func->lowPC = attr->value;
2183       break;
2184     case DW_AT_high_pc:
2185       func->highPC = attr->value;
2186       break;
2187     case DW_AT_prototyped:
2188       break;
2189     case DW_AT_decl_file:
2190       func->file = attr->value;
2191       break;
2192     case DW_AT_decl_line:
2193       func->line = attr->value;
2194       break;
2195     case DW_AT_external:
2196       func->external = attr->flag;
2197       break;
2198     case DW_AT_frame_base:
2199       func->frameBase = attr->block;
2200       break;
2201     case DW_AT_type:
2202       func->returnType = elfParseType(unit, attr->value);
2203       break;
2204     case DW_AT_abstract_origin:
2205       elfGetFunctionAttributes(unit, attr->value, func);
2206       break;
2207     case DW_AT_declaration:
2208       declaration = attr->flag;
2209       break;
2210     case DW_AT_inline:
2211     case DW_AT_specification:
2212     case DW_AT_artificial:
2213     case DW_AT_proc_body:
2214     case DW_AT_save_offset:
2215     case DW_AT_user_2002:
2216     case DW_AT_virtuality:
2217     case DW_AT_containing_type:
2218     case DW_AT_accessibility:
2219       // todo;
2220       break;
2221     case DW_AT_vtable_elem_location:
2222       free(attr->block);
2223       break;
2224     default:
2225       fprintf(stderr, "Unknown function attribute %02x\n", attr->name);
2226       break;
2227     }
2228   }
2229 
2230   if(declaration) {
2231     elfCleanUp(func);
2232     free(func);
2233     *f = NULL;
2234 
2235     while(1) {
2236       u32 abbrevNum = elfReadLEB128(data, &bytes);
2237       data += bytes;
2238 
2239       if(!abbrevNum) {
2240         return data;
2241       }
2242 
2243       abbrev = elfGetAbbrev(unit->abbrevs, abbrevNum);
2244 
2245       data = elfSkipData(data, abbrev, unit->abbrevs);
2246     }
2247   }
2248 
2249   if(abbrev->hasChildren) {
2250     int nesting = 1;
2251     Object *lastParam = NULL;
2252     Object *lastVar = NULL;
2253 
2254     while(nesting) {
2255       u32 abbrevNum = elfReadLEB128(data, &bytes);
2256       data += bytes;
2257 
2258       if(!abbrevNum) {
2259         nesting--;
2260         continue;
2261       }
2262 
2263       abbrev = elfGetAbbrev(unit->abbrevs, abbrevNum);
2264 
2265       switch(abbrev->tag) {
2266       CASE_TYPE_TAG: // no need to parse types. only parsed when used
2267       case DW_TAG_label: // not needed
2268         data = elfSkipData(data, abbrev, unit->abbrevs);
2269         break;
2270       case DW_TAG_subprogram:
2271         {
2272           Function *fnc=NULL;
2273           data = elfParseFunction(data, abbrev, unit, &fnc);
2274           if(fnc != NULL) {
2275             if(unit->lastFunction == NULL)
2276               unit->functions = fnc;
2277             else
2278               unit->lastFunction->next = fnc;
2279             unit->lastFunction = fnc;
2280           }
2281         }
2282         break;
2283       case DW_TAG_lexical_block:
2284         {
2285           data = elfParseBlock(data, abbrev, unit, func, &lastVar);
2286         }
2287         break;
2288       case DW_TAG_formal_parameter:
2289         {
2290           Object *o;
2291           data = elfParseObject(data, abbrev, unit, &o);
2292           if(func->parameters)
2293             lastParam->next = o;
2294           else
2295             func->parameters = o;
2296           lastParam = o;
2297         }
2298         break;
2299       case DW_TAG_variable:
2300         {
2301           Object *o;
2302           data = elfParseObject(data, abbrev, unit, &o);
2303           if(func->variables)
2304             lastVar->next = o;
2305           else
2306             func->variables = o;
2307           lastVar = o;
2308         }
2309         break;
2310       case DW_TAG_unspecified_parameters:
2311       case DW_TAG_inlined_subroutine:
2312         {
2313           // todo
2314           for(int i = 0; i < abbrev->numAttrs; i++) {
2315             data = elfReadAttribute(data,  &abbrev->attrs[i]);
2316             if(abbrev->attrs[i].form == DW_FORM_block1)
2317               free(abbrev->attrs[i].block);
2318           }
2319 
2320           if(abbrev->hasChildren)
2321             nesting++;
2322         }
2323         break;
2324       default:
2325         {
2326           fprintf(stderr, "Unknown function TAG %02x\n", abbrev->tag);
2327           data = elfSkipData(data, abbrev, unit->abbrevs);
2328         }
2329         break;
2330       }
2331     }
2332   }
2333   return data;
2334 }
2335 
elfParseUnknownData(u8 * data,ELFAbbrev * abbrev,ELFAbbrev ** abbrevs)2336 u8 *elfParseUnknownData(u8 *data, ELFAbbrev *abbrev, ELFAbbrev **abbrevs)
2337 {
2338   int i;
2339   int bytes;
2340   //  switch(abbrev->tag) {
2341   //  default:
2342     fprintf(stderr, "Unknown TAG %02x\n", abbrev->tag);
2343 
2344     for(i = 0; i < abbrev->numAttrs; i++) {
2345       data = elfReadAttribute(data,  &abbrev->attrs[i]);
2346       if(abbrev->attrs[i].form == DW_FORM_block1)
2347         free(abbrev->attrs[i].block);
2348     }
2349 
2350     if(abbrev->hasChildren) {
2351       int nesting = 1;
2352       while(nesting) {
2353         u32 abbrevNum = elfReadLEB128(data, &bytes);
2354         data += bytes;
2355 
2356         if(!abbrevNum) {
2357           nesting--;
2358           continue;
2359         }
2360 
2361         abbrev = elfGetAbbrev(abbrevs, abbrevNum);
2362 
2363         fprintf(stderr, "Unknown TAG %02x\n", abbrev->tag);
2364 
2365         for(i = 0; i < abbrev->numAttrs; i++) {
2366           data = elfReadAttribute(data,  &abbrev->attrs[i]);
2367           if(abbrev->attrs[i].form == DW_FORM_block1)
2368             free(abbrev->attrs[i].block);
2369         }
2370 
2371         if(abbrev->hasChildren) {
2372           nesting++;
2373         }
2374       }
2375     }
2376     //  }
2377   return data;
2378 }
2379 
elfParseCompileUnitChildren(u8 * data,CompileUnit * unit)2380 u8 *elfParseCompileUnitChildren(u8 *data, CompileUnit *unit)
2381 {
2382   int bytes;
2383   u32 abbrevNum = elfReadLEB128(data, &bytes);
2384   data += bytes;
2385   Object *lastObj = NULL;
2386   while(abbrevNum) {
2387     ELFAbbrev *abbrev = elfGetAbbrev(unit->abbrevs, abbrevNum);
2388     switch(abbrev->tag) {
2389     case DW_TAG_subprogram:
2390       {
2391         Function *func = NULL;
2392         data = elfParseFunction(data, abbrev, unit, &func);
2393         if(func != NULL) {
2394           if(unit->lastFunction)
2395             unit->lastFunction->next = func;
2396           else
2397             unit->functions = func;
2398           unit->lastFunction = func;
2399         }
2400       }
2401       break;
2402     CASE_TYPE_TAG:
2403       data = elfSkipData(data, abbrev, unit->abbrevs);
2404       break;
2405     case DW_TAG_variable:
2406       {
2407         Object *var = NULL;
2408         data = elfParseObject(data, abbrev, unit, &var);
2409         if(lastObj)
2410           lastObj->next = var;
2411         else
2412           unit->variables = var;
2413         lastObj = var;
2414       }
2415       break;
2416     default:
2417       data = elfParseUnknownData(data, abbrev, unit->abbrevs);
2418       break;
2419     }
2420 
2421     abbrevNum = elfReadLEB128(data, &bytes);
2422     data += bytes;
2423   }
2424   return data;
2425 }
2426 
2427 
elfParseCompUnit(u8 * data,u8 * abbrevData)2428 CompileUnit *elfParseCompUnit(u8 *data, u8 *abbrevData)
2429 {
2430   int bytes;
2431   u8 *top = data;
2432 
2433   u32 length = elfRead4Bytes(data);
2434   data += 4;
2435 
2436   u16 version = elfRead2Bytes(data);
2437   data += 2;
2438 
2439   u32 offset = elfRead4Bytes(data);
2440   data += 4;
2441 
2442   u8 addrSize = *data++;
2443 
2444   if(version != 2) {
2445     fprintf(stderr, "Unsupported debugging information version %d\n", version);
2446     return NULL;
2447   }
2448 
2449   if(addrSize != 4) {
2450     fprintf(stderr, "Unsupported address size %d\n", addrSize);
2451     return NULL;
2452   }
2453 
2454   ELFAbbrev **abbrevs = elfReadAbbrevs(abbrevData, offset);
2455 
2456   u32 abbrevNum = elfReadLEB128(data, &bytes);
2457   data += bytes;
2458 
2459   ELFAbbrev *abbrev = elfGetAbbrev(abbrevs, abbrevNum);
2460 
2461   CompileUnit *unit = (CompileUnit *)calloc(sizeof(CompileUnit), 1);
2462   unit->top = top;
2463   unit->length = length;
2464   unit->abbrevs = abbrevs;
2465   unit->next = NULL;
2466 
2467   elfCurrentUnit = unit;
2468 
2469   int i;
2470 
2471   for(i = 0; i < abbrev->numAttrs; i++) {
2472     ELFAttr *attr = &abbrev->attrs[i];
2473     data = elfReadAttribute(data, attr);
2474 
2475     switch(attr->name) {
2476     case DW_AT_name:
2477       unit->name = attr->string;
2478       break;
2479     case DW_AT_stmt_list:
2480       unit->hasLineInfo = true;
2481       unit->lineInfo = attr->value;
2482       break;
2483     case DW_AT_low_pc:
2484       unit->lowPC = attr->value;
2485       break;
2486     case DW_AT_high_pc:
2487       unit->highPC = attr->value;
2488       break;
2489     case DW_AT_compdir:
2490       unit->compdir = attr->string;
2491       break;
2492       // ignore
2493     case DW_AT_language:
2494     case DW_AT_producer:
2495     case DW_AT_macro_info:
2496     case DW_AT_entry_pc:
2497       break;
2498     default:
2499       fprintf(stderr, "Unknown attribute %02x\n", attr->name);
2500       break;
2501     }
2502   }
2503 
2504   if(abbrev->hasChildren)
2505     elfParseCompileUnitChildren(data, unit);
2506 
2507   return unit;
2508 }
2509 
elfParseAranges(u8 * data)2510 void elfParseAranges(u8 *data)
2511 {
2512   ELFSectionHeader *sh = elfGetSectionByName(".debug_aranges");
2513   if(sh == NULL) {
2514     fprintf(stderr, "No aranges found\n");
2515     return;
2516   }
2517 
2518   data = elfReadSection(data, sh);
2519   u8 *end = data + READ32LE(&sh->size);
2520 
2521   int max = 4;
2522   ARanges *ranges = (ARanges *)calloc(sizeof(ARanges), 4);
2523 
2524   int index = 0;
2525 
2526   while(data < end) {
2527     u32 len = elfRead4Bytes(data);
2528     data += 4;
2529     //    u16 version = elfRead2Bytes(data);
2530     data += 2;
2531     u32 offset = elfRead4Bytes(data);
2532     data += 4;
2533     //    u8 addrSize = *data++;
2534     //    u8 segSize = *data++;
2535     data += 2; // remove if uncommenting above
2536     data += 4;
2537     ranges[index].count = (len-20)/8;
2538     ranges[index].offset = offset;
2539     ranges[index].ranges = (ARange *)calloc(sizeof(ARange), (len-20)/8);
2540     int i = 0;
2541     while(true) {
2542       u32 addr = elfRead4Bytes(data);
2543       data += 4;
2544       u32 len = elfRead4Bytes(data);
2545       data += 4;
2546       if(addr == 0 && len == 0)
2547         break;
2548       ranges[index].ranges[i].lowPC = addr;
2549       ranges[index].ranges[i].highPC = addr+len;
2550       i++;
2551     }
2552     index++;
2553     if(index == max) {
2554       max += 4;
2555       ranges = (ARanges *)realloc(ranges, max*sizeof(ARanges));
2556     }
2557   }
2558   elfDebugInfo->numRanges = index;
2559   elfDebugInfo->ranges = ranges;
2560 }
2561 
elfReadSymtab(u8 * data)2562 void elfReadSymtab(u8 *data)
2563 {
2564   ELFSectionHeader *sh = elfGetSectionByName(".symtab");
2565   int table = READ32LE(&sh->link);
2566 
2567   char *strtable = (char *)elfReadSection(data, elfGetSectionByNumber(table));
2568 
2569   ELFSymbol *symtab = (ELFSymbol *)elfReadSection(data, sh);
2570 
2571   int count = READ32LE(&sh->size) / sizeof(ELFSymbol);
2572   elfSymbolsCount = 0;
2573 
2574   elfSymbols = (Symbol *)malloc(sizeof(Symbol)*count);
2575 
2576   int i;
2577 
2578   for(i = 0; i < count; i++) {
2579     ELFSymbol *s = &symtab[i];
2580     int type = s->info & 15;
2581     int binding = s->info >> 4;
2582 
2583     if(binding) {
2584       Symbol *sym = &elfSymbols[elfSymbolsCount];
2585       sym->name = &strtable[READ32LE(&s->name)];
2586       sym->binding = binding;
2587       sym->type = type;
2588       sym->value = READ32LE(&s->value);
2589       sym->size = READ32LE(&s->size);
2590       elfSymbolsCount++;
2591     }
2592   }
2593   for(i = 0; i < count; i++) {
2594     ELFSymbol *s = &symtab[i];
2595     int bind = s->info>>4;
2596     int type = s->info & 15;
2597 
2598     if(!bind) {
2599       Symbol *sym = &elfSymbols[elfSymbolsCount];
2600       sym->name = &strtable[READ32LE(&s->name)];
2601       sym->binding = (s->info >> 4);
2602       sym->type = type;
2603       sym->value = READ32LE(&s->value);
2604       sym->size = READ32LE(&s->size);
2605       elfSymbolsCount++;
2606     }
2607   }
2608   elfSymbolsStrTab = strtable;
2609   //  free(symtab);
2610 }
2611 
elfReadProgram(ELFHeader * eh,u8 * data,int & size,bool parseDebug)2612 bool elfReadProgram(ELFHeader *eh, u8 *data, int& size, bool parseDebug)
2613 {
2614   int count = READ16LE(&eh->e_phnum);
2615   int i;
2616 
2617   if(READ32LE(&eh->e_entry) == 0x2000000)
2618     cpuIsMultiBoot = true;
2619 
2620   // read program headers... should probably move this code down
2621   u8 *p = data + READ32LE(&eh->e_phoff);
2622   size = 0;
2623   for(i = 0; i < count; i++) {
2624     ELFProgramHeader *ph = (ELFProgramHeader *)p;
2625     p += sizeof(ELFProgramHeader);
2626     if(READ16LE(&eh->e_phentsize) != sizeof(ELFProgramHeader)) {
2627       p += READ16LE(&eh->e_phentsize) - sizeof(ELFProgramHeader);
2628     }
2629 
2630     //    printf("PH %d %08x %08x %08x %08x %08x %08x %08x %08x\n",
2631     //     i, ph->type, ph->offset, ph->vaddr, ph->paddr,
2632     //     ph->filesz, ph->memsz, ph->flags, ph->align);
2633     if(cpuIsMultiBoot) {
2634       if(READ32LE(&ph->paddr) >= 0x2000000 &&
2635          READ32LE(&ph->paddr) <= 0x203ffff) {
2636         memcpy(&workRAM[READ32LE(&ph->paddr) & 0x3ffff],
2637                data + READ32LE(&ph->offset),
2638                READ32LE(&ph->filesz));
2639         size += READ32LE(&ph->filesz);
2640       }
2641     } else {
2642       if(READ32LE(&ph->paddr) >= 0x8000000 &&
2643          READ32LE(&ph->paddr) <= 0x9ffffff) {
2644         memcpy(&rom[READ32LE(&ph->paddr) & 0x1ffffff],
2645                data + READ32LE(&ph->offset),
2646                READ32LE(&ph->filesz));
2647         size += READ32LE(&ph->filesz);
2648       }
2649     }
2650   }
2651 
2652   char *stringTable = NULL;
2653 
2654   // read section headers
2655   p = data + READ32LE(&eh->e_shoff);
2656   count = READ16LE(&eh->e_shnum);
2657 
2658   ELFSectionHeader **sh = (ELFSectionHeader **)
2659     malloc(sizeof(ELFSectionHeader *) * count);
2660 
2661   for(i = 0; i < count; i++) {
2662     sh[i] = (ELFSectionHeader *)p;
2663     p += sizeof(ELFSectionHeader);
2664     if(READ16LE(&eh->e_shentsize) != sizeof(ELFSectionHeader))
2665       p += READ16LE(&eh->e_shentsize) - sizeof(ELFSectionHeader);
2666   }
2667 
2668   if(READ16LE(&eh->e_shstrndx) != 0) {
2669     stringTable = (char *)elfReadSection(data,
2670                                          sh[READ16LE(&eh->e_shstrndx)]);
2671   }
2672 
2673   elfSectionHeaders = sh;
2674   elfSectionHeadersStringTable = stringTable;
2675   elfSectionHeadersCount = count;
2676 
2677   for(i = 0; i < count; i++) {
2678     //    printf("SH %d %-20s %08x %08x %08x %08x %08x %08x %08x %08x\n",
2679     //   i, &stringTable[sh[i]->name], sh[i]->name, sh[i]->type,
2680     //   sh[i]->flags, sh[i]->addr, sh[i]->offset, sh[i]->size,
2681     //   sh[i]->link, sh[i]->info);
2682     if(READ32LE(&sh[i]->flags) & 2) { // load section
2683       if(cpuIsMultiBoot) {
2684         if(READ32LE(&sh[i]->addr) >= 0x2000000 &&
2685            READ32LE(&sh[i]->addr) <= 0x203ffff) {
2686           memcpy(&workRAM[READ32LE(&sh[i]->addr) & 0x3ffff], data +
2687                  READ32LE(&sh[i]->offset),
2688                  READ32LE(&sh[i]->size));
2689                    size += READ32LE(&sh[i]->size);
2690         }
2691       } else {
2692         if(READ32LE(&sh[i]->addr) >= 0x8000000 &&
2693            READ32LE(&sh[i]->addr) <= 0x9ffffff) {
2694           memcpy(&rom[READ32LE(&sh[i]->addr) & 0x1ffffff],
2695                  data + READ32LE(&sh[i]->offset),
2696                  READ32LE(&sh[i]->size));
2697           size += READ32LE(&sh[i]->size);
2698         }
2699       }
2700     }
2701   }
2702 
2703   if(parseDebug) {
2704     fprintf(stderr, "Parsing debug info\n");
2705 
2706     ELFSectionHeader *dbgHeader = elfGetSectionByName(".debug_info");
2707     if(dbgHeader == NULL) {
2708       fprintf(stderr, "Cannot find debug information\n");
2709       goto end;
2710     }
2711 
2712     ELFSectionHeader *h = elfGetSectionByName(".debug_abbrev");
2713     if(h == NULL) {
2714       fprintf(stderr, "Cannot find abbreviation table\n");
2715       goto end;
2716     }
2717 
2718     elfDebugInfo = (DebugInfo *)calloc(sizeof(DebugInfo), 1);
2719     u8 *abbrevdata = elfReadSection(data, h);
2720 
2721     h = elfGetSectionByName(".debug_str");
2722 
2723     if(h == NULL)
2724       elfDebugStrings = NULL;
2725     else
2726       elfDebugStrings = (char *)elfReadSection(data, h);
2727 
2728     u8 *debugdata = elfReadSection(data, dbgHeader);
2729 
2730     elfDebugInfo->debugdata = data;
2731     elfDebugInfo->infodata = debugdata;
2732 
2733     u32 total = READ32LE(&dbgHeader->size);
2734     u8 *end = debugdata + total;
2735     u8 *ddata = debugdata;
2736 
2737     CompileUnit *last = NULL;
2738     CompileUnit *unit = NULL;
2739 
2740     while(ddata < end) {
2741       unit = elfParseCompUnit(ddata, abbrevdata);
2742       unit->offset = (u32)(ddata-debugdata);
2743       elfParseLineInfo(unit, data);
2744       if(last == NULL)
2745         elfCompileUnits = unit;
2746       else
2747         last->next = unit;
2748       last = unit;
2749       ddata += 4 + unit->length;
2750     }
2751     elfParseAranges(data);
2752     CompileUnit *comp = elfCompileUnits;
2753     while(comp) {
2754       ARanges *r = elfDebugInfo->ranges;
2755       for(int i = 0; i < elfDebugInfo->numRanges; i++)
2756         if(r[i].offset == comp->offset) {
2757           comp->ranges = &r[i];
2758           break;
2759         }
2760       comp = comp->next;
2761     }
2762     elfParseCFA(data);
2763     elfReadSymtab(data);
2764   }
2765  end:
2766   if(sh) {
2767     free(sh);
2768   }
2769 
2770   elfSectionHeaders = NULL;
2771   elfSectionHeadersStringTable = NULL;
2772   elfSectionHeadersCount = 0;
2773 
2774   return true;
2775 }
2776 
2777 extern bool parseDebug;
2778 
elfRead(const char * name,int & siz,FILE * f)2779 bool elfRead(const char *name, int& siz, FILE *f)
2780 {
2781   fseek(f, 0, SEEK_END);
2782   long size = ftell(f);
2783   elfFileData = (u8 *)malloc(size);
2784   fseek(f, 0, SEEK_SET);
2785   int res = fread(elfFileData, 1, size, f);
2786   fclose(f);
2787 
2788   if (res < 0)
2789   {
2790     free(elfFileData);
2791     elfFileData = NULL;
2792     return false;
2793   }
2794 
2795   ELFHeader *header = (ELFHeader *)elfFileData;
2796 
2797   if(READ32LE(&header->magic) != 0x464C457F ||
2798      READ16LE(&header->e_machine) != 40 ||
2799      header->clazz != 1) {
2800     systemMessage(0, N_("Not a valid ELF file %s"), name);
2801     free(elfFileData);
2802     elfFileData = NULL;
2803     return false;
2804   }
2805 
2806   if(!elfReadProgram(header, elfFileData, siz, parseDebug)) {
2807     free(elfFileData);
2808     elfFileData = NULL;
2809     return false;
2810   }
2811 
2812   return true;
2813 }
2814 
elfCleanUp(Object * o)2815 void elfCleanUp(Object *o)
2816 {
2817   free(o->location);
2818 }
2819 
elfCleanUp(Function * func)2820 void elfCleanUp(Function *func)
2821 {
2822   Object *o = func->parameters;
2823   while(o) {
2824     elfCleanUp(o);
2825     Object *next = o->next;
2826     free(o);
2827     o = next;
2828   }
2829 
2830   o = func->variables;
2831   while(o) {
2832     elfCleanUp(o);
2833     Object *next = o->next;
2834     free(o);
2835     o = next;
2836   }
2837   free(func->frameBase);
2838 }
2839 
elfCleanUp(ELFAbbrev ** abbrevs)2840 void elfCleanUp(ELFAbbrev **abbrevs)
2841 {
2842   for(int i = 0; i < 121; i++) {
2843     ELFAbbrev *abbrev = abbrevs[i];
2844 
2845     while(abbrev) {
2846       free(abbrev->attrs);
2847       ELFAbbrev *next = abbrev->next;
2848       free(abbrev);
2849 
2850       abbrev = next;
2851     }
2852   }
2853 }
2854 
elfCleanUp(Type * t)2855 void elfCleanUp(Type *t)
2856 {
2857   switch(t->type) {
2858   case TYPE_function:
2859     if(t->function) {
2860       Object *o = t->function->args;
2861       while(o) {
2862         elfCleanUp(o);
2863         Object *next = o->next;
2864         free(o);
2865         o = next;
2866       }
2867       free(t->function);
2868     }
2869     break;
2870   case TYPE_array:
2871     if(t->array) {
2872       free(t->array->bounds);
2873       free(t->array);
2874     }
2875     break;
2876   case TYPE_struct:
2877   case TYPE_union:
2878     if(t->structure) {
2879       for(int i = 0; i < t->structure->memberCount; i++) {
2880         free(t->structure->members[i].location);
2881       }
2882       free(t->structure->members);
2883       free(t->structure);
2884     }
2885     break;
2886   case TYPE_enum:
2887     if(t->enumeration) {
2888       free(t->enumeration->members);
2889       free(t->enumeration);
2890     }
2891     break;
2892   case TYPE_base:
2893   case TYPE_pointer:
2894   case TYPE_void:
2895   case TYPE_reference:
2896     break; // nothing to do
2897   }
2898 }
2899 
elfCleanUp(CompileUnit * comp)2900 void elfCleanUp(CompileUnit *comp)
2901 {
2902   elfCleanUp(comp->abbrevs);
2903   free(comp->abbrevs);
2904   Function *func = comp->functions;
2905   while(func) {
2906     elfCleanUp(func);
2907     Function *next = func->next;
2908     free(func);
2909     func = next;
2910   }
2911   Type *t = comp->types;
2912   while(t) {
2913     elfCleanUp(t);
2914     Type *next = t->next;
2915     free(t);
2916     t = next;
2917   }
2918   Object *o = comp->variables;
2919   while(o) {
2920     elfCleanUp(o);
2921     Object *next = o->next;
2922     free(o);
2923     o = next;
2924   }
2925   if(comp->lineInfoTable) {
2926     free(comp->lineInfoTable->lines);
2927     free(comp->lineInfoTable->files);
2928     free(comp->lineInfoTable);
2929   }
2930 }
2931 
elfCleanUp()2932 void elfCleanUp()
2933 {
2934   CompileUnit *comp = elfCompileUnits;
2935 
2936   while(comp) {
2937     elfCleanUp(comp);
2938     CompileUnit *next = comp->next;
2939     free(comp);
2940     comp = next;
2941   }
2942   elfCompileUnits = NULL;
2943   free(elfSymbols);
2944   elfSymbols = NULL;
2945   //  free(elfSymbolsStrTab);
2946   elfSymbolsStrTab = NULL;
2947 
2948   elfDebugStrings = NULL;
2949   if(elfDebugInfo) {
2950     int num = elfDebugInfo->numRanges;
2951     int i;
2952     for(i = 0; i < num; i++) {
2953       free(elfDebugInfo->ranges[i].ranges);
2954     }
2955     free(elfDebugInfo->ranges);
2956     free(elfDebugInfo);
2957     elfDebugInfo = NULL;
2958   }
2959 
2960   if(elfFdes) {
2961     if(elfFdeCount) {
2962       for(int i = 0; i < elfFdeCount; i++)
2963         free(elfFdes[i]);
2964     }
2965     free(elfFdes);
2966 
2967     elfFdes = NULL;
2968     elfFdeCount = 0;
2969   }
2970 
2971   ELFcie *cie = elfCies;
2972   while(cie) {
2973     ELFcie *next = cie->next;
2974     free(cie);
2975     cie = next;
2976   }
2977   elfCies = NULL;
2978 
2979   if(elfFileData) {
2980     free(elfFileData);
2981     elfFileData = NULL;
2982   }
2983 }
2984