macho-0.22: Parser for Mach-O object format.

Data.Macho

Description

Data.Macho is a module for parsing a ByteString of a Mach-O file into a Macho record.

Synopsis

Documentation

parseMacho :: ByteString -> MachoSource

Parse a ByteString of a Mach-O object into a Macho record.

data Macho Source

Constructors

Macho 

Fields

m_header :: MachoHeader

Header information.

m_commands :: [LC_COMMAND]

List of load commands describing Mach-O contents.

Instances

data MachoHeader Source

Constructors

MachoHeader 

Fields

mh_cputype :: CPU_TYPE

CPU family the Mach-O executes on.

mh_cpusubtype :: CPU_SUBTYPE

Specific CPU type the Mach-O executes on.

mh_filetype :: MH_FILETYPE

Type of Mach-o file.

mh_flags :: [MH_FLAGS]

Flags.

data LC_COMMAND Source

Constructors

LC_SEGMENT MachoSegment

segment of this file to be mapped

LC_SYMTAB [MachoSymbol] ByteString

static link-edit symbol table and stab info

LC_THREAD [(Word32, [Word32])]

thread state information (list of (flavor, [long]) pairs)

LC_UNIXTHREAD [(Word32, [Word32])]

unix thread state information (includes a stack) (list of (flavor, [long] pairs)

LC_DYSYMTAB MachoDynamicSymbolTable

dynamic link-edit symbol table info

LC_LOAD_DYLIB String Word32 Word32 Word32

load a dynamically linked shared library (name, timestamp, current version, compatibility version)

LC_ID_DYLIB String Word32 Word32 Word32

dynamically linked shared lib ident (name, timestamp, current version, compatibility version)

LC_LOAD_DYLINKER String

load a dynamic linker (name of dynamic linker)

LC_ID_DYLINKER String

dynamic linker identification (name of dynamic linker)

LC_PREBOUND_DYLIB String [Word8]

modules prebound for a dynamically linked shared library (name, list of module indices)

LC_ROUTINES Word32 Word32

image routines (virtual address of initialization routine, module index where it resides)

LC_SUB_FRAMEWORK String

sub framework (name)

LC_SUB_UMBRELLA String

sub umbrella (name)

LC_SUB_CLIENT String

sub client (name)

LC_SUB_LIBRARY String

sub library (name)

LC_TWOLEVEL_HINTS [(Word32, Word32)]

two-level namespace lookup hints (list of (subimage index, symbol table index) pairs

LC_PREBIND_CKSUM Word32

prebind checksum (checksum)

LC_LOAD_WEAK_DYLIB String Word32 Word32 Word32

load a dynamically linked shared library that is allowed to be missing (symbols are weak imported) (name, timestamp, current version, compatibility version)

LC_SEGMENT_64 MachoSegment

64-bit segment of this file to mapped

LC_ROUTINES_64 Word64 Word64

64-bit image routines (virtual address of initialization routine, module index where it resides)

LC_UUID [Word8]

the uuid for an image or its corresponding dsym file (8 element list of bytes)

LC_RPATH String

runpath additions (path)

LC_CODE_SIGNATURE Word32 Word32

local of code signature

LC_SEGMENT_SPLIT_INFO Word32 Word32

local of info to split segments

data MH_FLAGS Source

Constructors

MH_NOUNDEFS

the object file has no undefined references

MH_INCRLINK

the object file is the output of an incremental link against a base file and can't be link edited again

MH_DYLDLINK

the object file is input for the dynamic linker and can't be staticly link edited again

MH_BINDATLOAD

the object file's undefined references are bound by the dynamic linker when loaded.

MH_PREBOUND

the file has its dynamic undefined references prebound.

MH_SPLIT_SEGS

the file has its read-only and read-write segments split

MH_TWOLEVEL

the image is using two-level name space bindings

MH_FORCE_FLAT

the executable is forcing all images to use flat name space bindings

MH_NOMULTIDEFS

this umbrella guarantees no multiple defintions of symbols in its sub-images so the two-level namespace hints can always be used.

MH_NOFIXPREBINDING

do not have dyld notify the prebinding agent about this executable

MH_PREBINDABLE

the binary is not prebound but can have its prebinding redone. only used when MH_PREBOUND is not set.

MH_ALLMODSBOUND

indicates that this binary binds to all two-level namespace modules of its dependent libraries. only used when MH_PREBINDABLE and MH_TWOLEVEL are both set.

MH_SUBSECTIONS_VIA_SYMBOLS

safe to divide up the sections into sub-sections via symbols for dead code stripping

MH_CANONICAL

the binary has been canonicalized via the unprebind operation

MH_WEAK_DEFINES

the final linked image contains external weak symbols

MH_BINDS_TO_WEAK

the final linked image uses weak symbols

MH_ALLOW_STACK_EXECUTION

When this bit is set, all stacks in the task will be given stack execution privilege. Only used in MH_EXECUTE filetypes.

MH_ROOT_SAFE

When this bit is set, the binary declares it is safe for use in processes with uid zero

MH_SETUID_SAFE

When this bit is set, the binary declares it is safe for use in processes when issetugid() is true

MH_NO_REEXPORTED_DYLIBS

When this bit is set on a dylib, the static linker does not need to examine dependent dylibs to see if any are re-exported

MH_PIE

When this bit is set, the OS will load the main executable at a random address. Only used in MH_EXECUTE filetypes.

Instances

data VM_PROT Source

Constructors

VM_PROT_READ

read permission

VM_PROT_WRITE

write permission

VM_PROT_EXECUTE

execute permission

Instances

data MachoSegment Source

Constructors

MachoSegment 

Fields

seg_segname :: String

segment name

seg_vmaddr :: Word64

virtual address where the segment is loaded

seg_vmsize :: Word64

size of segment at runtime

seg_fileoff :: Word64

file offset of the segment

seg_filesize :: Word64

size of segment in file

seg_maxprot :: [VM_PROT]

maximum virtual memory protection

seg_initprot :: [VM_PROT]

initial virtual memory protection

seg_flags :: [SG_FLAG]

segment flags

seg_sections :: [MachoSection]

sections owned by this segment

data SG_FLAG Source

Constructors

SG_HIGHVM

The file contents for this segment is for the high part of the VM space, the low part is zero filled (for stacks in core files).

SG_NORELOC

This segment has nothing that was relocated in it and nothing relocated to it, that is it may be safely replaced without relocation.

Instances

data MachoSection Source

Constructors

MachoSection 

Fields

sec_sectname :: String

name of section

sec_segname :: String

name of segment that should own this section

sec_addr :: Word64

virtual memoy address for section

sec_size :: Word64

size of section

sec_align :: Int

alignment required by section (literal form, not power of two, e.g. 8 not 3)

sec_relocs :: [Relocation]

relocations for this section

sec_type :: S_TYPE

type of section

sec_user_attrs :: [S_USER_ATTR]

user attributes of section

sec_sys_attrs :: [S_SYS_ATTR]

system attibutes of section

data S_TYPE Source

Constructors

S_REGULAR

regular section

S_ZEROFILL

zero fill on demand section

S_CSTRING_LITERALS

section with only literal C strings

S_4BYTE_LITERALS

section with only 4 byte literals

S_8BYTE_LITERALS

section with only 8 byte literals

S_LITERAL_POINTERS

section with only pointers to literals

S_NON_LAZY_SYMBOL_POINTERS

section with only non-lazy symbol pointers

S_LAZY_SYMBOL_POINTERS

section with only lazy symbol pointers

S_SYMBOL_STUBS

section with only symbol stubs, bte size of stub in the reserved2 field

S_MOD_INIT_FUNC_POINTERS

section with only function pointers for initialization

S_MOD_TERM_FUNC_POINTERS

section with only function pointers for termination

S_COALESCED

section contains symbols that are to be coalesced

S_GB_ZEROFILL

zero fill on demand section (that can be larger than 4 gigabytes)

S_INTERPOSING

section with only pairs of function pointers for interposing

S_16BYTE_LITERALS

section with only 16 byte literals

S_DTRACE_DOF

section contains DTrace Object Format

S_LAZY_DYLIB_SYMBOL_POINTERS

section with only lazy symbol pointers to lazy loaded dylibs

Instances

data S_USER_ATTR Source

Constructors

S_ATTR_PURE_INSTRUCTIONS

section contains only true machine instructions

S_ATTR_NO_TOC

setion contains coalesced symbols that are not to be in a ranlib table of contents

S_ATTR_STRIP_STATIC_SYMS

ok to strip static symbols in this section in files with the MH_DYLDLINK flag

S_ATTR_NO_DEAD_STRIP

no dead stripping

S_ATTR_LIVE_SUPPORT

blocks are live if they reference live blocks

S_ATTR_SELF_MODIFYING_CODE

used with i386 code stubs written on by dyld

S_ATTR_DEBUG

a debug section

data S_SYS_ATTR Source

Constructors

S_ATTR_SOME_INSTRUCTIONS

section contains soem machine instructions

S_ATTR_EXT_RELOC

section has external relocation entries

S_ATTR_LOC_RELOC

section has local relocation entries

data N_TYPE Source

Constructors

N_UNDF

undefined symbol, n_sect is 0

N_ABS

absolute symbol, does not need relocation, n_sect is 0

N_SECT

symbol is defined in section n_sect

N_PBUD

symbol is undefined and the image is using a prebound value for the symbol, n_sect is 0

N_INDR

symbol is defined to be the same as another symbol. n_value is a string table offset indicating the name of that symbol

N_GSYM

stab global symbol: name,,0,type,0

N_FNAME

stab procedure name (f77 kludge): name,,0,0,0

N_FUN

stab procedure: name,,n_sect,linenumber,address

N_STSYM

stab static symbol: name,,n_sect,type,address

N_LCSYM

stab .lcomm symbol: name,,n_sect,type,address

N_BNSYM

stab begin nsect sym: 0,,n_sect,0,address

N_OPT

stab emitted with gcc2_compiled and in gcc source

N_RSYM

stab register sym: name,,0,type,register

N_SLINE

stab src line: 0,,n_sect,linenumber,address

N_ENSYM

stab end nsect sym: 0,,n_sect,0,address

N_SSYM

stab structure elt: name,,0,type,struct_offset

N_SO

stab source file name: name,,n_sect,0,address

N_OSO

stab object file name: name,,0,0,st_mtime

N_LSYM

stab local sym: name,,0,type,offset

N_BINCL

stab include file beginning: name,,0,0,sum

N_SOL

stab #included file name: name,,n_sect,0,address

N_PARAMS

stab compiler parameters: name,,0,0,0

N_VERSION

stab compiler version: name,,0,0,0

N_OLEVEL

stab compiler -O level: name,,0,0,0

N_PSYM

stab parameter: name,,0,type,offset

N_EINCL

stab include file end: name,,0,0,0

N_ENTRY

stab alternate entry: name,,n_sect,linenumber,address

N_LBRAC

stab left bracket: 0,,0,nesting level,address

N_EXCL

stab deleted include file: name,,0,0,sum

N_RBRAC

stab right bracket: 0,,0,nesting level,address

N_BCOMM

stab begin common: name,,0,0,0

N_ECOMM

stab end common: name,,n_sect,0,0

N_ECOML

stab end common (local name): 0,,n_sect,0,address

N_LENG

stab second stab entry with length information

N_PC

stab global pascal symbol: name,,0,subtype,line

Instances

data REFERENCE_FLAG Source

Constructors

REFERENCE_FLAG_UNDEFINED_NON_LAZY

reference to an external non-lazy symbol

REFERENCE_FLAG_UNDEFINED_LAZY

reference to an external lazy symbol

REFERENCE_FLAG_DEFINED

symbol is defined in this module

REFERENCE_FLAG_PRIVATE_DEFINED

symbol is defined in this module and visible only to modules within this shared library

REFERENCE_FLAG_PRIVATE_UNDEFINED_NON_LAZY

reference to an external non-lazy symbol and visible only to modules within this shared library

REFERENCE_FLAG_PRIVATE_UNDEFINED_LAZY

reference to an external lazy symbol and visible only to modules within this shared library

REFERENCED_DYNAMICALLY

set for all symbols referenced by dynamic loader APIs

N_WEAK_REF

indicates the symbol is a weak reference, set to 0 if definition cannot be found

N_WEAK_DEF

indicates the symbol is a weak definition, will be overridden by a strong definition at link-time

LIBRARY_ORDINAL Word16

for two-level mach-o objects, specifies the index of the library in which this symbol is defined. zero specifies current image.

data MachoSymbol Source

Constructors

MachoSymbol 

Fields

sym_name :: String

symbol name

sym_type :: N_TYPE

symbol type

sym_pext :: Bool

true if limited global scope

sym_ext :: Bool

true if external symbol

sym_sect :: Word8

section index where the symbol can be found

sym_flags :: Either Word16 [REFERENCE_FLAG]

for stab entries, Left Word16 is the uninterpreted flags field, otherwise Right [REFERENCE_FLAG] are the symbol flags

sym_value :: Word64

symbol value, 32-bit symbol values are promoted to 64-bit for simpliciy

data DylibModule Source

Constructors

DylibModule 

Fields

dylib_module_name_offset :: Word32

module name string table offset

dylib_ext_def_sym :: (Word32, Word32)

(initial, count) pair of symbol table indices for externally defined symbols

dylib_ref_sym :: (Word32, Word32)

(initial, count) pair of symbol table indices for referenced symbols

dylib_local_sym :: (Word32, Word32)

(initial, count) pair of symbol table indices for local symbols

dylib_ext_rel :: (Word32, Word32)

(initial, count) pair of symbol table indices for externally referenced symbols

dylib_init :: (Word32, Word32)

(initial, count) pair of symbol table indices for the index of the module init section and the number of init pointers

dylib_term :: (Word32, Word32)

(initial, count) pair of symbol table indices for the index of the module term section and the number of term pointers

dylib_objc_module_info_addr :: Word32

statically linked address of the start of the data for this module in the __module_info section in the __OBJC segment

dylib_objc_module_info_size :: Word64

number of bytes of data for this module that are used in the __module_info section in the __OBJC segment

data Relocation Source

Constructors

RelocationInfo 

Fields

ri_address :: Int32

offset from start of section to place to be relocated

ri_symbolnum :: Word32

index into symbol or section table

ri_pcrel :: Bool

indicates if the item to be relocated is part of an instruction containing PC-relative addressing

ri_length :: Word32

length of item containing address to be relocated (literal form (4) instead of power of two (2))

ri_extern :: Bool

indicates whether symbolnum is an index into the symbol table (True) or section table (False)

ri_type :: R_TYPE

relocation type

ScatteredRelocationInfo 

Fields

rs_pcrel :: Bool

indicates if the item to be relocated is part of an instruction containing PC-relative addressing

rs_length :: Word32

length of item containing address to be relocated (literal form (4) instead of power of two (2))

rs_type :: R_TYPE

relocation type

rs_address :: Word32

offset from start of section to place to be relocated

rs_value :: Int32

address of the relocatable expression for the item in the file that needs to be updated if the address is changed

data MachoDynamicSymbolTable Source

Constructors

MachoDynamicSymbolTable 

Fields

localSyms :: (Word32, Word32)

symbol table index and count for local symbols

extDefSyms :: (Word32, Word32)

symbol table index and count for externally defined symbols

undefSyms :: (Word32, Word32)

symbol table index and count for undefined symbols

tocEntries :: [(Word32, Word32)]

list of symbol index and module index pairs

modules :: [DylibModule]

modules

extRefSyms :: [Word32]

list of external reference symbol indices

indirectSyms :: [Word32]

list of indirect symbol indices

extRels :: [Relocation]

external locations

locRels :: [Relocation]

local relocations

data MH_FILETYPE Source

Constructors

MH_OBJECT

relocatable object file

MH_EXECUTE

demand paged executable file

MH_CORE

core file

MH_PRELOAD

preloaded executable file

MH_DYLIB

dynamically bound shared library

MH_DYLINKER

dynamic link editor

MH_BUNDLE

dynamically bound bundle file

MH_DYLIB_STUB

shared library stub for static. linking only, no section contents

MH_DSYM

companion file with only debug. sections