melf-1.3.0: An Elf parser
Copyright(c) Aleksey Makarov 2021
LicenseBSD 3-Clause License
Maintaineraleksey.makarov@gmail.com
Stabilityexperimental
Portabilityportable
Safe HaskellSafe-Inferred
LanguageHaskell2010

Data.Elf.Headers

Description

Parse headers and table entries of ELF files

Synopsis

Data definition

elfMagic :: Be Word32 Source #

The first 4 bytes of the ELF file

data ElfClass Source #

ELF class. Tells if ELF defines 32- or 64-bit objects

Constructors

ELFCLASS32

32-bit ELF format

ELFCLASS64

64-bit ELF format

Instances

Instances details
Show ElfClass Source # 
Instance details

Defined in Data.Elf.Headers

Binary ElfClass Source # 
Instance details

Defined in Data.Elf.Headers

Methods

put :: ElfClass -> Put #

get :: Get ElfClass #

putList :: [ElfClass] -> Put #

Eq ElfClass Source # 
Instance details

Defined in Data.Elf.Headers

data ElfData Source #

ELF data. Specifies the endianness of the ELF data

Constructors

ELFDATA2LSB

Little-endian ELF format

ELFDATA2MSB

Big-endian ELF format

Instances

Instances details
Show ElfData Source # 
Instance details

Defined in Data.Elf.Headers

Binary ElfData Source # 
Instance details

Defined in Data.Elf.Headers

Methods

put :: ElfData -> Put #

get :: Get ElfData #

putList :: [ElfData] -> Put #

Eq ElfData Source # 
Instance details

Defined in Data.Elf.Headers

Methods

(==) :: ElfData -> ElfData -> Bool #

(/=) :: ElfData -> ElfData -> Bool #

Singletons

data SingElfClass :: ElfClass -> Type where Source #

Singletons for ElfClass

Constructors

SELFCLASS32 

Fields

SELFCLASS64 

Fields

class (Typeable c, Typeable (WordXX c), Data (WordXX c), Show (WordXX c), Read (WordXX c), Eq (WordXX c), Ord (WordXX c), Bounded (WordXX c), Enum (WordXX c), Num (WordXX c), Integral (WordXX c), Real (WordXX c), Bits (WordXX c), FiniteBits (WordXX c), Binary (Be (WordXX c)), Binary (Le (WordXX c))) => SingElfClassI (c :: ElfClass) where Source #

SingElfClassI a is defined for each constructor of ElfClass. It defines WordXX a, which is Word32 for ELFCLASS32 and Word64 for ELFCLASS64. Also it defines singletons for each of the ElfClass type.

Associated Types

type WordXX c = r | r -> c Source #

Instances

Instances details
SingElfClassI 'ELFCLASS32 Source # 
Instance details

Defined in Data.Elf.Headers

Associated Types

type WordXX 'ELFCLASS32 = (r :: Type) Source #

SingElfClassI 'ELFCLASS64 Source # 
Instance details

Defined in Data.Elf.Headers

Associated Types

type WordXX 'ELFCLASS64 = (r :: Type) Source #

withSingElfClass :: SingElfClassI c => (SingElfClass c -> r) -> r Source #

A convenience function useful when we need to name a singleton value multiple times. Without this function, each use of sing could potentially refer to a different singleton, and one has to use type signatures (often with ScopedTypeVariables) to ensure that they are the same. See also withSingI

withSingElfClassI :: SingElfClass c -> (SingElfClassI c => r) -> r Source #

Convenience function for creating a context with an implicit singleton available. See also withSing

fromSingElfClass :: SingElfClass c -> ElfClass Source #

Convert a singleton to its unrefined version. See also fromSing

withElfClass :: ElfClass -> (forall c. SingElfClassI c => SingElfClass c -> r) -> r Source #

Use this instead of toSing

Types of ELF header

data HeaderXX c Source #

Parsed ELF header

Constructors

HeaderXX 

Fields

headerSize :: Num a => ElfClass -> a Source #

Size of ELF header.

data Header Source #

Header is a sigma type where the first entry defines the type of the second one

Constructors

forall a. Header (SingElfClass a) (HeaderXX a) 

Instances

Instances details
Binary Header Source # 
Instance details

Defined in Data.Elf.Headers

Methods

put :: Header -> Put #

get :: Get Header #

putList :: [Header] -> Put #

Types of ELF tables

Section table

data SectionXX c Source #

Parsed ELF section table entry

Constructors

SectionXX 

Fields

Instances

Instances details
SingElfClassI a => Binary (Be (SectionXX a)) Source # 
Instance details

Defined in Data.Elf.Headers

Methods

put :: Be (SectionXX a) -> Put #

get :: Get (Be (SectionXX a)) #

putList :: [Be (SectionXX a)] -> Put #

SingElfClassI a => Binary (Le (SectionXX a)) Source # 
Instance details

Defined in Data.Elf.Headers

Methods

put :: Le (SectionXX a) -> Put #

get :: Get (Le (SectionXX a)) #

putList :: [Le (SectionXX a)] -> Put #

sectionTableEntrySize :: Num a => ElfClass -> a Source #

Size of section table entry.

Segment table

data SegmentXX c Source #

Parsed ELF segment table entry

Constructors

SegmentXX 

Fields

Instances

Instances details
SingElfClassI a => Binary (Be (SegmentXX a)) Source # 
Instance details

Defined in Data.Elf.Headers

Methods

put :: Be (SegmentXX a) -> Put #

get :: Get (Be (SegmentXX a)) #

putList :: [Be (SegmentXX a)] -> Put #

SingElfClassI a => Binary (Le (SegmentXX a)) Source # 
Instance details

Defined in Data.Elf.Headers

Methods

put :: Le (SegmentXX a) -> Put #

get :: Get (Le (SegmentXX a)) #

putList :: [Le (SegmentXX a)] -> Put #

segmentTableEntrySize :: Num a => ElfClass -> a Source #

Size of segment table entry.

Sybmol table

data SymbolXX c Source #

Parsed ELF symbol table entry

Constructors

SymbolXX 

Fields

Instances

Instances details
SingElfClassI a => Binary (Be (SymbolXX a)) Source # 
Instance details

Defined in Data.Elf.Headers

Methods

put :: Be (SymbolXX a) -> Put #

get :: Get (Be (SymbolXX a)) #

putList :: [Be (SymbolXX a)] -> Put #

SingElfClassI a => Binary (Le (SymbolXX a)) Source # 
Instance details

Defined in Data.Elf.Headers

Methods

put :: Le (SymbolXX a) -> Put #

get :: Get (Le (SymbolXX a)) #

putList :: [Le (SymbolXX a)] -> Put #

symbolTableEntrySize :: Num a => ElfClass -> a Source #

Size of symbol table entry.

Relocation table

data RelaXX c Source #

Parsed relocation table entry (ElfXX_Rela)

Constructors

RelaXX 

Fields

Instances

Instances details
SingElfClassI a => Binary (Be (RelaXX a)) Source # 
Instance details

Defined in Data.Elf.Headers

Methods

put :: Be (RelaXX a) -> Put #

get :: Get (Be (RelaXX a)) #

putList :: [Be (RelaXX a)] -> Put #

SingElfClassI a => Binary (Le (RelaXX a)) Source # 
Instance details

Defined in Data.Elf.Headers

Methods

put :: Le (RelaXX a) -> Put #

get :: Get (Le (RelaXX a)) #

putList :: [Le (RelaXX a)] -> Put #

relocationTableAEntrySize :: forall a. SingElfClassI a => WordXX a Source #

Size of RelaXX a in bytes.

Parse header and section and segment tables

data Headers Source #

Sigma type to hold the ELF header and section and segment tables for a given ElfClass.

Constructors

forall a. Headers (SingElfClass a) (HeaderXX a) [SectionXX a] [SegmentXX a] 

parseHeaders :: MonadThrow m => ByteString -> m Headers Source #

Parse ELF file and produce header and section and segment tables

Parse/serialize array of data

BList is an internal newtype for [a] that is an instance of Binary. When serializing, the Binary instance for BList does not write the length of the array to the stream. Instead, parser just reads all the stream till the end.

parseBList Source #

Arguments

:: (MonadThrow m, Binary (Le a), Binary (Be a)) 
=> ElfData

Tells if parser should expect big or little endian data

-> ByteString

Data for parsing

-> m [a] 

Parse an array

serializeBList Source #

Arguments

:: (Binary (Le a), Binary (Be a)) 
=> ElfData

Tells if serializer should tread the data as bit or little endian

-> [a]

The array to serialize

-> ByteString 

Serialize an array

Misc helpers

sectionIsSymbolTable :: ElfSectionType -> Bool Source #

Test if the section with such integer value of section type field (sType) contains symbol table

getSectionData Source #

Arguments

:: SingElfClassI a 
=> ByteString

ELF file

-> SectionXX a

Parsed section entry

-> ByteString

Section Data

Get section data

getString Source #

Arguments

:: ByteString

Section data of a string table section

-> Int64

Offset to the start of the string in that data

-> String 

Get string from string table

wordSize :: Num a => ElfClass -> a Source #

Size of WordXX a in bytes.