data-elf-0.2: Executable and Linkable Format (ELF) data structures.

Safe HaskellNone
LanguageHaskell2010

Data.Elf

Contents

Description

This module provides ELF data structures and (de)serialization routines.

Synopsis

File class

newtype FileClass Source #

File class.

Constructors

FileClass 

Fields

Instances

Bounded FileClass Source # 
Enum FileClass Source # 
Eq FileClass Source # 
Data FileClass Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FileClass -> c FileClass #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FileClass #

toConstr :: FileClass -> Constr #

dataTypeOf :: FileClass -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FileClass) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FileClass) #

gmapT :: (forall b. Data b => b -> b) -> FileClass -> FileClass #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FileClass -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FileClass -> r #

gmapQ :: (forall d. Data d => d -> u) -> FileClass -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FileClass -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FileClass -> m FileClass #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FileClass -> m FileClass #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FileClass -> m FileClass #

Ord FileClass Source # 
Read FileClass Source # 
Show FileClass Source # 
Ix FileClass Source # 

invalidFileClass :: FileClass Source #

Invalid class (ELFCLASSNONE).

elf32FileClass :: FileClass Source #

ELF32 class (ELFCLASS32).

elf64FileClass :: FileClass Source #

ELF64 class (ELFCLASS64).

class (Typeable c, Typeable (Addr c), Data (Addr c), Typeable (Off c), Data (Off c), Typeable (UnSymIx c), Data (UnSymIx c), Typeable (UnRelType c), Data (UnRelType c), Show (Addr c), Read (Addr c), Show (Off c), Read (Off c), Show (UnSymIx c), Read (UnSymIx c), Show (UnRelType c), Read (UnRelType c), Eq (Addr c), Ord (Addr c), Bounded (Addr c), Enum (Addr c), Num (Addr c), Integral (Addr c), Real (Addr c), Bits (Addr c), FiniteBits (Addr c), Eq (Off c), Ord (Off c), Bounded (Off c), Enum (Off c), Num (Off c), Integral (Off c), Real (Off c), Bits (Off c), FiniteBits (Off c), Eq (UnSymIx c), Ord (UnSymIx c), Bounded (UnSymIx c), Enum (UnSymIx c), Ix (UnSymIx c), Num (UnSymIx c), Integral (UnSymIx c), Real (UnSymIx c), Bits (UnSymIx c), FiniteBits (UnSymIx c), Eq (UnRelType c), Ord (UnRelType c), Bounded (UnRelType c), Enum (UnRelType c), Ix (UnRelType c)) => IsFileClass c where Source #

File class type-level index.

Minimal complete definition

fileClass

Associated Types

type Addr c Source #

type Off c Source #

type UnSymIx c Source #

type UnRelType c Source #

Instances

IsFileClass Elf64 Source # 

Associated Types

type Addr Elf64 :: * Source #

type Off Elf64 :: * Source #

type UnSymIx Elf64 :: * Source #

type UnRelType Elf64 :: * Source #

IsFileClass Elf32 Source # 

Associated Types

type Addr Elf32 :: * Source #

type Off Elf32 :: * Source #

type UnSymIx Elf32 :: * Source #

type UnRelType Elf32 :: * Source #

data Elf32 Source #

32-bit ELF class type-level index.

Constructors

Elf32 

Instances

Data Elf32 Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Elf32 -> c Elf32 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Elf32 #

toConstr :: Elf32 -> Constr #

dataTypeOf :: Elf32 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Elf32) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Elf32) #

gmapT :: (forall b. Data b => b -> b) -> Elf32 -> Elf32 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Elf32 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Elf32 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Elf32 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Elf32 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Elf32 -> m Elf32 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Elf32 -> m Elf32 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Elf32 -> m Elf32 #

Serializable RelaEnt32 Source # 

Methods

put :: Serializer s => RelaEnt32 -> s #

Serializable RelEnt32 Source # 

Methods

put :: Serializer s => RelEnt32 -> s #

Serializable SymEnt32 Source # 

Methods

put :: Serializer s => SymEnt32 -> s #

Serializable SecHdr32 Source # 

Methods

put :: Serializer s => SecHdr32 -> s #

Serializable ProgHdr32 Source # 

Methods

put :: Serializer s => ProgHdr32 -> s #

Serializable FileHdr32 Source # 

Methods

put :: Serializer s => FileHdr32 -> s #

SizedSerializable RelaEnt32 Source # 

Methods

size :: Proxy * RelaEnt32 -> Int #

SizedSerializable RelEnt32 Source # 

Methods

size :: Proxy * RelEnt32 -> Int #

SizedSerializable SymEnt32 Source # 

Methods

size :: Proxy * SymEnt32 -> Int #

SizedSerializable SecHdr32 Source # 

Methods

size :: Proxy * SecHdr32 -> Int #

SizedSerializable ProgHdr32 Source # 

Methods

size :: Proxy * ProgHdr32 -> Int #

SizedSerializable FileHdr32 Source # 

Methods

size :: Proxy * FileHdr32 -> Int #

Deserializable RelaEnt32 Source # 

Methods

get :: Deserializer μ => μ RelaEnt32 #

Deserializable RelEnt32 Source # 

Methods

get :: Deserializer μ => μ RelEnt32 #

Deserializable SymEnt32 Source # 

Methods

get :: Deserializer μ => μ SymEnt32 #

Deserializable SecHdr32 Source # 

Methods

get :: Deserializer μ => μ SecHdr32 #

Deserializable ProgHdr32 Source # 

Methods

get :: Deserializer μ => μ ProgHdr32 #

Deserializable FileHdr32 Source # 

Methods

get :: Deserializer μ => μ FileHdr32 #

IsFileClass Elf32 Source # 

Associated Types

type Addr Elf32 :: * Source #

type Off Elf32 :: * Source #

type UnSymIx Elf32 :: * Source #

type UnRelType Elf32 :: * Source #

type Addr Elf32 Source # 
type Off Elf32 Source # 
type UnSymIx Elf32 Source # 
type UnRelType Elf32 Source # 

anElf32 :: Proxy Elf32 Source #

Elf32 proxy value.

data Elf64 Source #

64-bit ELF class type-level index.

Constructors

Elf64 

Instances

Data Elf64 Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Elf64 -> c Elf64 #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Elf64 #

toConstr :: Elf64 -> Constr #

dataTypeOf :: Elf64 -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Elf64) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Elf64) #

gmapT :: (forall b. Data b => b -> b) -> Elf64 -> Elf64 #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Elf64 -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Elf64 -> r #

gmapQ :: (forall d. Data d => d -> u) -> Elf64 -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Elf64 -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Elf64 -> m Elf64 #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Elf64 -> m Elf64 #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Elf64 -> m Elf64 #

Serializable RelaEnt64 Source # 

Methods

put :: Serializer s => RelaEnt64 -> s #

Serializable RelEnt64 Source # 

Methods

put :: Serializer s => RelEnt64 -> s #

Serializable SymEnt64 Source # 

Methods

put :: Serializer s => SymEnt64 -> s #

Serializable SecHdr64 Source # 

Methods

put :: Serializer s => SecHdr64 -> s #

Serializable ProgHdr64 Source # 

Methods

put :: Serializer s => ProgHdr64 -> s #

Serializable FileHdr64 Source # 

Methods

put :: Serializer s => FileHdr64 -> s #

SizedSerializable RelaEnt64 Source # 

Methods

size :: Proxy * RelaEnt64 -> Int #

SizedSerializable RelEnt64 Source # 

Methods

size :: Proxy * RelEnt64 -> Int #

SizedSerializable SymEnt64 Source # 

Methods

size :: Proxy * SymEnt64 -> Int #

SizedSerializable SecHdr64 Source # 

Methods

size :: Proxy * SecHdr64 -> Int #

SizedSerializable ProgHdr64 Source # 

Methods

size :: Proxy * ProgHdr64 -> Int #

SizedSerializable FileHdr64 Source # 

Methods

size :: Proxy * FileHdr64 -> Int #

Deserializable RelaEnt64 Source # 

Methods

get :: Deserializer μ => μ RelaEnt64 #

Deserializable RelEnt64 Source # 

Methods

get :: Deserializer μ => μ RelEnt64 #

Deserializable SymEnt64 Source # 

Methods

get :: Deserializer μ => μ SymEnt64 #

Deserializable SecHdr64 Source # 

Methods

get :: Deserializer μ => μ SecHdr64 #

Deserializable ProgHdr64 Source # 

Methods

get :: Deserializer μ => μ ProgHdr64 #

Deserializable FileHdr64 Source # 

Methods

get :: Deserializer μ => μ FileHdr64 #

IsFileClass Elf64 Source # 

Associated Types

type Addr Elf64 :: * Source #

type Off Elf64 :: * Source #

type UnSymIx Elf64 :: * Source #

type UnRelType Elf64 :: * Source #

type Addr Elf64 Source # 
type Off Elf64 Source # 
type UnSymIx Elf64 Source # 
type UnRelType Elf64 Source # 

anElf64 :: Proxy Elf64 Source #

Elf64 proxy value.

File header

File type

newtype FileType Source #

File type.

Constructors

FileType 

Fields

Instances

Bounded FileType Source # 
Enum FileType Source # 
Eq FileType Source # 
Data FileType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FileType -> c FileType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c FileType #

toConstr :: FileType -> Constr #

dataTypeOf :: FileType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c FileType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c FileType) #

gmapT :: (forall b. Data b => b -> b) -> FileType -> FileType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FileType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FileType -> r #

gmapQ :: (forall d. Data d => d -> u) -> FileType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FileType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FileType -> m FileType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FileType -> m FileType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FileType -> m FileType #

Ord FileType Source # 
Read FileType Source # 
Show FileType Source # 
Ix FileType Source # 

noneFileType :: FileType Source #

No file type (ET_NONE).

relFileType :: FileType Source #

Relocatable object file (ET_REL).

execFileType :: FileType Source #

Executable file (ET_EXEC).

dynFileType :: FileType Source #

Shared object file (ET_DYN).

coreFileType :: FileType Source #

Core file (ET_CORE).

loOsFileType :: FileType Source #

First environment-specific type (ET_LOOS).

hiOsFileType :: FileType Source #

Last environment-specific type (ET_HIOS).

loProcFileType :: FileType Source #

First processor-specific type (ET_LOPROC).

hiProcFileType :: FileType Source #

Last processor-specific type (ET_HIPROC).

Machine code

newtype Machine Source #

Machine architecture.

Constructors

Machine 

Fields

Instances

Bounded Machine Source # 
Enum Machine Source # 
Eq Machine Source # 

Methods

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

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

Data Machine Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Machine -> c Machine #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Machine #

toConstr :: Machine -> Constr #

dataTypeOf :: Machine -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Machine) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Machine) #

gmapT :: (forall b. Data b => b -> b) -> Machine -> Machine #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Machine -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Machine -> r #

gmapQ :: (forall d. Data d => d -> u) -> Machine -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Machine -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Machine -> m Machine #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Machine -> m Machine #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Machine -> m Machine #

Ord Machine Source # 
Read Machine Source # 
Show Machine Source # 
Ix Machine Source # 

undefMachine :: Machine Source #

No machine (EM_NONE).

i386Machine :: Machine Source #

Intel 80386 (EM_386).

amd64Machine :: Machine Source #

AMD x86-64 (EM_X86_64).

Machine flags

newtype MachFlags Source #

Architecture-specific flags.

Constructors

MachFlags 

Fields

Instances

Eq MachFlags Source # 
Data MachFlags Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> MachFlags -> c MachFlags #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c MachFlags #

toConstr :: MachFlags -> Constr #

dataTypeOf :: MachFlags -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c MachFlags) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c MachFlags) #

gmapT :: (forall b. Data b => b -> b) -> MachFlags -> MachFlags #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> MachFlags -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> MachFlags -> r #

gmapQ :: (forall d. Data d => d -> u) -> MachFlags -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> MachFlags -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> MachFlags -> m MachFlags #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> MachFlags -> m MachFlags #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> MachFlags -> m MachFlags #

Read MachFlags Source # 
Show MachFlags Source # 
Flags MachFlags Source # 
BoundedFlags MachFlags Source # 

ELF version

newtype Version Source #

ELF version.

Constructors

Version 

Fields

Instances

Bounded Version Source # 
Enum Version Source # 
Eq Version Source # 

Methods

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

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

Data Version Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Version -> c Version #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Version #

toConstr :: Version -> Constr #

dataTypeOf :: Version -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Version) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Version) #

gmapT :: (forall b. Data b => b -> b) -> Version -> Version #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Version -> r #

gmapQ :: (forall d. Data d => d -> u) -> Version -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Version -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Version -> m Version #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Version -> m Version #

Ord Version Source # 
Read Version Source # 
Show Version Source # 
Ix Version Source # 

invalidVersion :: Version Source #

Invalid version.

Data encoding

newtype DataEnc Source #

Data encoding.

Constructors

DataEnc 

Fields

Instances

Bounded DataEnc Source # 
Enum DataEnc Source # 
Eq DataEnc Source # 

Methods

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

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

Data DataEnc Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DataEnc -> c DataEnc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DataEnc #

toConstr :: DataEnc -> Constr #

dataTypeOf :: DataEnc -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c DataEnc) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DataEnc) #

gmapT :: (forall b. Data b => b -> b) -> DataEnc -> DataEnc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DataEnc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DataEnc -> r #

gmapQ :: (forall d. Data d => d -> u) -> DataEnc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> DataEnc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> DataEnc -> m DataEnc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DataEnc -> m DataEnc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DataEnc -> m DataEnc #

Ord DataEnc Source # 
Read DataEnc Source # 
Show DataEnc Source # 
Ix DataEnc Source # 

invalidDataEnc :: DataEnc Source #

Invalid data encoding.

lsbDataEnc :: DataEnc Source #

Little-endian data encoding (ELFDATA2LSB).

msbDataEnc :: DataEnc Source #

Big-endian data encoding (ELFDATA2MSB).

Operating system ABI

newtype OsAbi Source #

System ABI.

Constructors

OsAbi 

Fields

Instances

Bounded OsAbi Source # 
Enum OsAbi Source # 
Eq OsAbi Source # 

Methods

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

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

Data OsAbi Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OsAbi -> c OsAbi #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c OsAbi #

toConstr :: OsAbi -> Constr #

dataTypeOf :: OsAbi -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c OsAbi) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c OsAbi) #

gmapT :: (forall b. Data b => b -> b) -> OsAbi -> OsAbi #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OsAbi -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OsAbi -> r #

gmapQ :: (forall d. Data d => d -> u) -> OsAbi -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> OsAbi -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> OsAbi -> m OsAbi #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OsAbi -> m OsAbi #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OsAbi -> m OsAbi #

Ord OsAbi Source # 

Methods

compare :: OsAbi -> OsAbi -> Ordering #

(<) :: OsAbi -> OsAbi -> Bool #

(<=) :: OsAbi -> OsAbi -> Bool #

(>) :: OsAbi -> OsAbi -> Bool #

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

max :: OsAbi -> OsAbi -> OsAbi #

min :: OsAbi -> OsAbi -> OsAbi #

Read OsAbi Source # 
Show OsAbi Source # 

Methods

showsPrec :: Int -> OsAbi -> ShowS #

show :: OsAbi -> String #

showList :: [OsAbi] -> ShowS #

Ix OsAbi Source # 

sysvOsAbi :: OsAbi Source #

System V (ELFOSABI_NONE).

hpuxOsAbi :: OsAbi Source #

HP-UX (ELFOSABI_HPUX).

netBsdOsAbi :: OsAbi Source #

NetBSD (ELFOSABI_NETBSD).

gnuOsAbi :: OsAbi Source #

GNU (ELFOSABI_GNU, ELFOSABI_LINUX).

solarisOsAbi :: OsAbi Source #

Solaris (ELFOSABI_SOLARIS).

aixOsAbi :: OsAbi Source #

AIX (ELFOSABI_AIX).

irixOsAbi :: OsAbi Source #

IRIX (ELFOSABI_IRIX).

freeBsdOsAbi :: OsAbi Source #

FreeBSD (ELFOSABI_FREEBSD).

tru64OsAbi :: OsAbi Source #

Tru64 UNIX (ELFOSABI_TRU64).

modestoOsAbi :: OsAbi Source #

Novell Modesto (ELFOSABI_MODESTO).

openBsdOsAbi :: OsAbi Source #

OpenBSD (ELFOSABI_OPENBSD).

openVmsOsAbi :: OsAbi Source #

OpenVMS (ELFOSABI_OPENVMS).

nskOsAbi :: OsAbi Source #

Hewlett-Packard Non-Stop Kernel (ELFOSABI_NSK).

arosOsAbi :: OsAbi Source #

Amiga Research OS (ELFOSABI_AROS).

fenixOsAbi :: OsAbi Source #

FenixOS (ELFOSABI_FENIXOS).

embedOsAbi :: OsAbi Source #

Standalone (embedded) application.

newtype AbiVer Source #

ABI version.

Constructors

AbiVer 

Fields

Instances

Bounded AbiVer Source # 
Enum AbiVer Source # 
Eq AbiVer Source # 

Methods

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

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

Data AbiVer Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AbiVer -> c AbiVer #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AbiVer #

toConstr :: AbiVer -> Constr #

dataTypeOf :: AbiVer -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c AbiVer) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AbiVer) #

gmapT :: (forall b. Data b => b -> b) -> AbiVer -> AbiVer #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AbiVer -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AbiVer -> r #

gmapQ :: (forall d. Data d => d -> u) -> AbiVer -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AbiVer -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AbiVer -> m AbiVer #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AbiVer -> m AbiVer #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AbiVer -> m AbiVer #

Ord AbiVer Source # 
Read AbiVer Source # 
Show AbiVer Source # 
Ix AbiVer Source # 

undefAbiVer :: AbiVer Source #

Undefined ABI version.

Identification

data Ident Source #

Identification.

Instances

Eq Ident Source # 

Methods

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

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

Data Ident Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ident -> c Ident #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Ident #

toConstr :: Ident -> Constr #

dataTypeOf :: Ident -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Ident) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Ident) #

gmapT :: (forall b. Data b => b -> b) -> Ident -> Ident #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ident -> r #

gmapQ :: (forall d. Data d => d -> u) -> Ident -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ident -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ident -> m Ident #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ident -> m Ident #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ident -> m Ident #

Read Ident Source # 
Show Ident Source # 

Methods

showsPrec :: Int -> Ident -> ShowS #

show :: Ident -> String #

showList :: [Ident] -> ShowS #

Serializable Ident Source # 

Methods

put :: Serializer s => Ident -> s #

SizedSerializable Ident Source # 

Methods

size :: Proxy * Ident -> Int #

Deserializable Ident Source # 

Methods

get :: Deserializer μ => μ Ident #

anIdent :: Proxy Ident Source #

Ident proxy value.

File header

data FileHdr c Source #

File header.

Instances

Serializable FileHdr64 Source # 

Methods

put :: Serializer s => FileHdr64 -> s #

Serializable FileHdr32 Source # 

Methods

put :: Serializer s => FileHdr32 -> s #

SizedSerializable FileHdr64 Source # 

Methods

size :: Proxy * FileHdr64 -> Int #

SizedSerializable FileHdr32 Source # 

Methods

size :: Proxy * FileHdr32 -> Int #

Deserializable FileHdr64 Source # 

Methods

get :: Deserializer μ => μ FileHdr64 #

Deserializable FileHdr32 Source # 

Methods

get :: Deserializer μ => μ FileHdr32 #

IsFileClass c => Eq (FileHdr c) Source # 

Methods

(==) :: FileHdr c -> FileHdr c -> Bool #

(/=) :: FileHdr c -> FileHdr c -> Bool #

(Data c, IsFileClass c) => Data (FileHdr c) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> FileHdr c -> c (FileHdr c) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (FileHdr c) #

toConstr :: FileHdr c -> Constr #

dataTypeOf :: FileHdr c -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (FileHdr c)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (FileHdr c)) #

gmapT :: (forall b. Data b => b -> b) -> FileHdr c -> FileHdr c #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> FileHdr c -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> FileHdr c -> r #

gmapQ :: (forall d. Data d => d -> u) -> FileHdr c -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> FileHdr c -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> FileHdr c -> m (FileHdr c) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> FileHdr c -> m (FileHdr c) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> FileHdr c -> m (FileHdr c) #

IsFileClass c => Read (FileHdr c) Source # 
IsFileClass c => Show (FileHdr c) Source # 

Methods

showsPrec :: Int -> FileHdr c -> ShowS #

show :: FileHdr c -> String #

showList :: [FileHdr c] -> ShowS #

type FileHdr32 = FileHdr Elf32 Source #

ELF32 file header.

type FileHdr64 = FileHdr Elf64 Source #

ELF64 file header.

Program header

Segment type

newtype SegType Source #

Segment type.

Constructors

SegType 

Fields

Instances

Bounded SegType Source # 
Enum SegType Source # 
Eq SegType Source # 

Methods

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

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

Data SegType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SegType -> c SegType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SegType #

toConstr :: SegType -> Constr #

dataTypeOf :: SegType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SegType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SegType) #

gmapT :: (forall b. Data b => b -> b) -> SegType -> SegType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SegType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SegType -> r #

gmapQ :: (forall d. Data d => d -> u) -> SegType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SegType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SegType -> m SegType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SegType -> m SegType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SegType -> m SegType #

Ord SegType Source # 
Read SegType Source # 
Show SegType Source # 
Ix SegType Source # 

unusedSegType :: SegType Source #

Unused program header entry (PT_NULL).

loadSegType :: SegType Source #

Loadable segment (PT_LOAD).

dynSegType :: SegType Source #

Dynamic linking tables (PT_DYNAMIC).

interpSegType :: SegType Source #

Program interpreter path name (PT_INTERP).

noteSegType :: SegType Source #

Note sections (PT_NOTE).

shlibSegType :: SegType Source #

A reserved segment type (PT_SHLIB).

phdrSegType :: SegType Source #

Program header table (PT_PHDR).

loOsSegType :: SegType Source #

First environment-specific segment type (PT_LOOS).

hiOsSegType :: SegType Source #

Last environment-specific segment type (PT_HIOS).

loProcSegType :: SegType Source #

First processor-specific segment type (PT_LOPROC).

hiProcSegType :: SegType Source #

Last processor-specific segment type (PT_HIPROC).

Segment flags

newtype SegFlags Source #

Segment flags.

Constructors

SegFlags 

Fields

Instances

Eq SegFlags Source # 
Data SegFlags Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SegFlags -> c SegFlags #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SegFlags #

toConstr :: SegFlags -> Constr #

dataTypeOf :: SegFlags -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SegFlags) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SegFlags) #

gmapT :: (forall b. Data b => b -> b) -> SegFlags -> SegFlags #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SegFlags -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SegFlags -> r #

gmapQ :: (forall d. Data d => d -> u) -> SegFlags -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SegFlags -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SegFlags -> m SegFlags #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SegFlags -> m SegFlags #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SegFlags -> m SegFlags #

Read SegFlags Source # 
Show SegFlags Source # 
Flags SegFlags Source # 
BoundedFlags SegFlags Source # 

execSegFlag :: SegFlags Source #

Execute permission (PF_X).

writeSegFlag :: SegFlags Source #

Write permission (PF_W).

readSegFlag :: SegFlags Source #

Read permission (PF_R).

osSegFlags :: SegFlags Source #

Environment-specific flags mask (PF_MASKOS).

procSegFlags :: SegFlags Source #

Processor-specific flags mask (PF_MASKPROC).

Program header

data ProgHdr c Source #

Program header table entry.

Constructors

ProgHdr 

Instances

Serializable ProgHdr64 Source # 

Methods

put :: Serializer s => ProgHdr64 -> s #

Serializable ProgHdr32 Source # 

Methods

put :: Serializer s => ProgHdr32 -> s #

SizedSerializable ProgHdr64 Source # 

Methods

size :: Proxy * ProgHdr64 -> Int #

SizedSerializable ProgHdr32 Source # 

Methods

size :: Proxy * ProgHdr32 -> Int #

Deserializable ProgHdr64 Source # 

Methods

get :: Deserializer μ => μ ProgHdr64 #

Deserializable ProgHdr32 Source # 

Methods

get :: Deserializer μ => μ ProgHdr32 #

IsFileClass c => Eq (ProgHdr c) Source # 

Methods

(==) :: ProgHdr c -> ProgHdr c -> Bool #

(/=) :: ProgHdr c -> ProgHdr c -> Bool #

(Data c, IsFileClass c) => Data (ProgHdr c) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ProgHdr c -> c (ProgHdr c) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (ProgHdr c) #

toConstr :: ProgHdr c -> Constr #

dataTypeOf :: ProgHdr c -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (ProgHdr c)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (ProgHdr c)) #

gmapT :: (forall b. Data b => b -> b) -> ProgHdr c -> ProgHdr c #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ProgHdr c -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ProgHdr c -> r #

gmapQ :: (forall d. Data d => d -> u) -> ProgHdr c -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ProgHdr c -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ProgHdr c -> m (ProgHdr c) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ProgHdr c -> m (ProgHdr c) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ProgHdr c -> m (ProgHdr c) #

IsFileClass c => Read (ProgHdr c) Source # 
IsFileClass c => Show (ProgHdr c) Source # 

Methods

showsPrec :: Int -> ProgHdr c -> ShowS #

show :: ProgHdr c -> String #

showList :: [ProgHdr c] -> ShowS #

type ProgHdr32 = ProgHdr Elf32 Source #

ELF32 program header table entry.

type ProgHdr64 = ProgHdr Elf64 Source #

ELF64 program header table entry.

Section header

String table index

type StrIx = Word32 Source #

String table index.

Section header table index

newtype SecIx Source #

Section header entry index.

Constructors

SecIx 

Fields

Instances

Bounded SecIx Source # 
Enum SecIx Source # 
Eq SecIx Source # 

Methods

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

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

Integral SecIx Source # 
Data SecIx Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SecIx -> c SecIx #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SecIx #

toConstr :: SecIx -> Constr #

dataTypeOf :: SecIx -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SecIx) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SecIx) #

gmapT :: (forall b. Data b => b -> b) -> SecIx -> SecIx #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SecIx -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SecIx -> r #

gmapQ :: (forall d. Data d => d -> u) -> SecIx -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SecIx -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SecIx -> m SecIx #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SecIx -> m SecIx #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SecIx -> m SecIx #

Num SecIx Source # 
Ord SecIx Source # 

Methods

compare :: SecIx -> SecIx -> Ordering #

(<) :: SecIx -> SecIx -> Bool #

(<=) :: SecIx -> SecIx -> Bool #

(>) :: SecIx -> SecIx -> Bool #

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

max :: SecIx -> SecIx -> SecIx #

min :: SecIx -> SecIx -> SecIx #

Read SecIx Source # 
Real SecIx Source # 

Methods

toRational :: SecIx -> Rational #

Show SecIx Source # 

Methods

showsPrec :: Int -> SecIx -> ShowS #

show :: SecIx -> String #

showList :: [SecIx] -> ShowS #

Ix SecIx Source # 
Bits SecIx Source # 
FiniteBits SecIx Source # 

undefSecIx :: SecIx Source #

Undefined section reference (SHN_UNDEF).

lastSecIx :: SecIx Source #

Last regular section index.

loOsSecIx :: SecIx Source #

First environment-specific section index (SHN_LOOS).

hiOsSecIx :: SecIx Source #

Last environment-specific section index (SHN_HIOS).

loProcSecIx :: SecIx Source #

First processor-specific section index (SHN_LOPROC).

hiProcSecIx :: SecIx Source #

Last processor-specific section index (SHN_HIPROC).

absSecIx :: SecIx Source #

Absolute value indicator (SHN_ABS).

commonSecIx :: SecIx Source #

Common block indicator (SHN_COMMON).

xIndexSecIx :: SecIx Source #

Escape value (SHN_XINDEX).

Section type

newtype SecType Source #

Section type.

Constructors

SecType 

Fields

Instances

Bounded SecType Source # 
Enum SecType Source # 
Eq SecType Source # 

Methods

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

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

Data SecType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SecType -> c SecType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SecType #

toConstr :: SecType -> Constr #

dataTypeOf :: SecType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SecType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SecType) #

gmapT :: (forall b. Data b => b -> b) -> SecType -> SecType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SecType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SecType -> r #

gmapQ :: (forall d. Data d => d -> u) -> SecType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SecType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SecType -> m SecType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SecType -> m SecType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SecType -> m SecType #

Ord SecType Source # 
Read SecType Source # 
Show SecType Source # 
Ix SecType Source # 

unusedSecType :: SecType Source #

Unused section (SHT_NULL).

progBitsSecType :: SecType Source #

Program information (SHT_PROGBITS).

symSecType :: SecType Source #

Symbol table (SHT_SYMTAB).

strSecType :: SecType Source #

String table (SHT_STRTAB).

relaSecType :: SecType Source #

Relocation entries (SHT_RELA).

hashSecType :: SecType Source #

Symbol hash table (SHT_HASH).

dynSecType :: SecType Source #

Dynamic linking table (SHT_DYNAMIC).

noteSecType :: SecType Source #

Note information (SHT_NOTE).

noBitsSecType :: SecType Source #

Uninitialized space (SHT_NOBITS).

relSecType :: SecType Source #

Relocation entries (SHT_REL).

shlibSecType :: SecType Source #

A reserved section type (SHT_SHLIB).

dynSymSecType :: SecType Source #

Dynamic loader symbol table (SHT_DYNSYM).

loOsSecType :: SecType Source #

First environment-specific section type (SHT_LOOS).

hiOsSecType :: SecType Source #

Last environment-specific section type (SHT_HIOS).

loProcSecType :: SecType Source #

First processor-specific section type (SHT_LOPROC).

hiProcSecType :: SecType Source #

Last processor-specific section type (SHT_HIPROC).

Section flags

newtype SecFlags Source #

Section flags.

Constructors

SecFlags 

Fields

Instances

Eq SecFlags Source # 
Data SecFlags Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SecFlags -> c SecFlags #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SecFlags #

toConstr :: SecFlags -> Constr #

dataTypeOf :: SecFlags -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SecFlags) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SecFlags) #

gmapT :: (forall b. Data b => b -> b) -> SecFlags -> SecFlags #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SecFlags -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SecFlags -> r #

gmapQ :: (forall d. Data d => d -> u) -> SecFlags -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SecFlags -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SecFlags -> m SecFlags #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SecFlags -> m SecFlags #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SecFlags -> m SecFlags #

Read SecFlags Source # 
Show SecFlags Source # 
Flags SecFlags Source # 
BoundedFlags SecFlags Source # 

writeSecFlag :: SecFlags Source #

Writable data (SHF_WRITE).

allocSecFlag :: SecFlags Source #

Allocated data (SHF_ALLOC).

execSecFlag :: SecFlags Source #

Executable instructions (SHF_EXECINSTR).

mergeSecFlag :: SecFlags Source #

Mergeable data (SHF_MERGE).

infoLinkSecFlag :: SecFlags Source #

Flag that indicates that shInfo is a section header table index. (SHF_INFO_LINK)

osSecFlags :: SecFlags Source #

Environment-specific flags mask (SHF_MASKOS).

procSecFlags :: SecFlags Source #

Processor-specific flags mask (SHF_MASKOS).

Section header

data SecHdr c Source #

Section header table entry.

Constructors

SecHdr 

Instances

Serializable SecHdr64 Source # 

Methods

put :: Serializer s => SecHdr64 -> s #

Serializable SecHdr32 Source # 

Methods

put :: Serializer s => SecHdr32 -> s #

SizedSerializable SecHdr64 Source # 

Methods

size :: Proxy * SecHdr64 -> Int #

SizedSerializable SecHdr32 Source # 

Methods

size :: Proxy * SecHdr32 -> Int #

Deserializable SecHdr64 Source # 

Methods

get :: Deserializer μ => μ SecHdr64 #

Deserializable SecHdr32 Source # 

Methods

get :: Deserializer μ => μ SecHdr32 #

IsFileClass c => Eq (SecHdr c) Source # 

Methods

(==) :: SecHdr c -> SecHdr c -> Bool #

(/=) :: SecHdr c -> SecHdr c -> Bool #

(Data c, IsFileClass c) => Data (SecHdr c) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SecHdr c -> c (SecHdr c) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SecHdr c) #

toConstr :: SecHdr c -> Constr #

dataTypeOf :: SecHdr c -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (SecHdr c)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SecHdr c)) #

gmapT :: (forall b. Data b => b -> b) -> SecHdr c -> SecHdr c #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SecHdr c -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SecHdr c -> r #

gmapQ :: (forall d. Data d => d -> u) -> SecHdr c -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SecHdr c -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SecHdr c -> m (SecHdr c) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SecHdr c -> m (SecHdr c) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SecHdr c -> m (SecHdr c) #

IsFileClass c => Read (SecHdr c) Source # 
IsFileClass c => Show (SecHdr c) Source # 

Methods

showsPrec :: Int -> SecHdr c -> ShowS #

show :: SecHdr c -> String #

showList :: [SecHdr c] -> ShowS #

type SecHdr32 = SecHdr Elf32 Source #

ELF32 section header table entry.

type SecHdr64 = SecHdr Elf64 Source #

ELF64 section header table entry.

zeroSecHdr :: IsFileClass c => SecHdr c Source #

Section header filled with zeros.

Symbol table

Symbol type

newtype SymType Source #

Symbol type.

Constructors

SymType 

Fields

Instances

Bounded SymType Source # 
Enum SymType Source # 
Eq SymType Source # 

Methods

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

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

Data SymType Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SymType -> c SymType #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SymType #

toConstr :: SymType -> Constr #

dataTypeOf :: SymType -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SymType) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SymType) #

gmapT :: (forall b. Data b => b -> b) -> SymType -> SymType #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SymType -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SymType -> r #

gmapQ :: (forall d. Data d => d -> u) -> SymType -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SymType -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SymType -> m SymType #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SymType -> m SymType #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SymType -> m SymType #

Ord SymType Source # 
Read SymType Source # 
Show SymType Source # 
Ix SymType Source # 

undefSymType :: SymType Source #

Undefined symbol type (STT_NOTYPE).

objSymType :: SymType Source #

Object (STT_OBJECT).

funSymType :: SymType Source #

Function (STT_FUNC).

secSymType :: SymType Source #

Section (STT_SECTION).

fileSymType :: SymType Source #

Source file name (STT_FILE).

commonSymType :: SymType Source #

Common block label (STT_COMMON).

tlsSymType :: SymType Source #

Thread-local storage (STT_TLS).

loOsSymType :: SymType Source #

First environment-specific symbol type (STT_LOOS).

hiOsSymType :: SymType Source #

Last environment-specific symbol type (STT_HIOS).

loProcSymType :: SymType Source #

First processor-specific symbol type (STT_LOPROC).

hiProcSymType :: SymType Source #

Last processor-specific symbol type (STT_HIPROC).

Symbol binding

newtype SymBind Source #

Symbol binding type.

Constructors

SymBind 

Fields

Instances

Bounded SymBind Source # 
Enum SymBind Source # 
Eq SymBind Source # 

Methods

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

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

Data SymBind Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SymBind -> c SymBind #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SymBind #

toConstr :: SymBind -> Constr #

dataTypeOf :: SymBind -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SymBind) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SymBind) #

gmapT :: (forall b. Data b => b -> b) -> SymBind -> SymBind #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SymBind -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SymBind -> r #

gmapQ :: (forall d. Data d => d -> u) -> SymBind -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SymBind -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SymBind -> m SymBind #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SymBind -> m SymBind #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SymBind -> m SymBind #

Ord SymBind Source # 
Read SymBind Source # 
Show SymBind Source # 
Ix SymBind Source # 

localSymBind :: SymBind Source #

Local symbol (STB_LOCAL).

globalSymBind :: SymBind Source #

Global symbol (STB_GLOBAL).

weakSymBind :: SymBind Source #

Lower precedence global symbol (STB_WEAK).

loOsSymBind :: SymBind Source #

First environment-specific symbol binding type (STB_LOOS).

hiOsSymBind :: SymBind Source #

Last environment-specific symbol binding type (STB_HIOS).

loProcSymBind :: SymBind Source #

First processor-specific symbol binding type (STB_LOPROC).

hiProcSymBind :: SymBind Source #

Last processor-specific symbol binding type (STB_HIPROC).

Symbol visibility

newtype SymVisi Source #

Symbol visibility.

Constructors

SymVisi 

Fields

Instances

Bounded SymVisi Source # 
Enum SymVisi Source # 
Eq SymVisi Source # 

Methods

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

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

Data SymVisi Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SymVisi -> c SymVisi #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SymVisi #

toConstr :: SymVisi -> Constr #

dataTypeOf :: SymVisi -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c SymVisi) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SymVisi) #

gmapT :: (forall b. Data b => b -> b) -> SymVisi -> SymVisi #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SymVisi -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SymVisi -> r #

gmapQ :: (forall d. Data d => d -> u) -> SymVisi -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SymVisi -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SymVisi -> m SymVisi #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SymVisi -> m SymVisi #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SymVisi -> m SymVisi #

Ord SymVisi Source # 
Read SymVisi Source # 
Show SymVisi Source # 
Ix SymVisi Source # 

defSymVisi :: SymVisi Source #

Default symbol visibility (specified by the binding type; STV_DEFAULT).

intSymVisi :: SymVisi Source #

Internal symbol visibility (processor-specific hidden type; STV_INTERNAL).

hiddenSymVisi :: SymVisi Source #

Hidden symbol (STV_HIDDEN).

protSymVisi :: SymVisi Source #

Protected symbol (STV_PROTECTED).

exportSymVisi :: SymVisi Source #

Global symbol (STV_EXPORTED).

singSymVisi :: SymVisi Source #

Global singleton symbol (STV_SINGLETON).

elimSymVisi :: SymVisi Source #

Extra hidden symbol (STV_ELIMINATE).

Symbol table index

newtype SymIx c Source #

Symbol table index.

Constructors

SymIx 

Fields

Instances

IsFileClass c => Bounded (SymIx c) Source # 

Methods

minBound :: SymIx c #

maxBound :: SymIx c #

IsFileClass c => Enum (SymIx c) Source # 

Methods

succ :: SymIx c -> SymIx c #

pred :: SymIx c -> SymIx c #

toEnum :: Int -> SymIx c #

fromEnum :: SymIx c -> Int #

enumFrom :: SymIx c -> [SymIx c] #

enumFromThen :: SymIx c -> SymIx c -> [SymIx c] #

enumFromTo :: SymIx c -> SymIx c -> [SymIx c] #

enumFromThenTo :: SymIx c -> SymIx c -> SymIx c -> [SymIx c] #

IsFileClass c => Eq (SymIx c) Source # 

Methods

(==) :: SymIx c -> SymIx c -> Bool #

(/=) :: SymIx c -> SymIx c -> Bool #

IsFileClass c => Integral (SymIx c) Source # 

Methods

quot :: SymIx c -> SymIx c -> SymIx c #

rem :: SymIx c -> SymIx c -> SymIx c #

div :: SymIx c -> SymIx c -> SymIx c #

mod :: SymIx c -> SymIx c -> SymIx c #

quotRem :: SymIx c -> SymIx c -> (SymIx c, SymIx c) #

divMod :: SymIx c -> SymIx c -> (SymIx c, SymIx c) #

toInteger :: SymIx c -> Integer #

(Data c, IsFileClass c) => Data (SymIx c) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SymIx c -> c (SymIx c) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SymIx c) #

toConstr :: SymIx c -> Constr #

dataTypeOf :: SymIx c -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (SymIx c)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SymIx c)) #

gmapT :: (forall b. Data b => b -> b) -> SymIx c -> SymIx c #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SymIx c -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SymIx c -> r #

gmapQ :: (forall d. Data d => d -> u) -> SymIx c -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SymIx c -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SymIx c -> m (SymIx c) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SymIx c -> m (SymIx c) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SymIx c -> m (SymIx c) #

IsFileClass c => Num (SymIx c) Source # 

Methods

(+) :: SymIx c -> SymIx c -> SymIx c #

(-) :: SymIx c -> SymIx c -> SymIx c #

(*) :: SymIx c -> SymIx c -> SymIx c #

negate :: SymIx c -> SymIx c #

abs :: SymIx c -> SymIx c #

signum :: SymIx c -> SymIx c #

fromInteger :: Integer -> SymIx c #

IsFileClass c => Ord (SymIx c) Source # 

Methods

compare :: SymIx c -> SymIx c -> Ordering #

(<) :: SymIx c -> SymIx c -> Bool #

(<=) :: SymIx c -> SymIx c -> Bool #

(>) :: SymIx c -> SymIx c -> Bool #

(>=) :: SymIx c -> SymIx c -> Bool #

max :: SymIx c -> SymIx c -> SymIx c #

min :: SymIx c -> SymIx c -> SymIx c #

IsFileClass c => Read (SymIx c) Source # 
IsFileClass c => Real (SymIx c) Source # 

Methods

toRational :: SymIx c -> Rational #

IsFileClass c => Show (SymIx c) Source # 

Methods

showsPrec :: Int -> SymIx c -> ShowS #

show :: SymIx c -> String #

showList :: [SymIx c] -> ShowS #

IsFileClass c => Ix (SymIx c) Source # 

Methods

range :: (SymIx c, SymIx c) -> [SymIx c] #

index :: (SymIx c, SymIx c) -> SymIx c -> Int #

unsafeIndex :: (SymIx c, SymIx c) -> SymIx c -> Int

inRange :: (SymIx c, SymIx c) -> SymIx c -> Bool #

rangeSize :: (SymIx c, SymIx c) -> Int #

unsafeRangeSize :: (SymIx c, SymIx c) -> Int

IsFileClass c => Bits (SymIx c) Source # 

Methods

(.&.) :: SymIx c -> SymIx c -> SymIx c #

(.|.) :: SymIx c -> SymIx c -> SymIx c #

xor :: SymIx c -> SymIx c -> SymIx c #

complement :: SymIx c -> SymIx c #

shift :: SymIx c -> Int -> SymIx c #

rotate :: SymIx c -> Int -> SymIx c #

zeroBits :: SymIx c #

bit :: Int -> SymIx c #

setBit :: SymIx c -> Int -> SymIx c #

clearBit :: SymIx c -> Int -> SymIx c #

complementBit :: SymIx c -> Int -> SymIx c #

testBit :: SymIx c -> Int -> Bool #

bitSizeMaybe :: SymIx c -> Maybe Int #

bitSize :: SymIx c -> Int #

isSigned :: SymIx c -> Bool #

shiftL :: SymIx c -> Int -> SymIx c #

unsafeShiftL :: SymIx c -> Int -> SymIx c #

shiftR :: SymIx c -> Int -> SymIx c #

unsafeShiftR :: SymIx c -> Int -> SymIx c #

rotateL :: SymIx c -> Int -> SymIx c #

rotateR :: SymIx c -> Int -> SymIx c #

popCount :: SymIx c -> Int #

IsFileClass c => FiniteBits (SymIx c) Source # 

undefSymIx :: IsFileClass c => SymIx c Source #

Undefined symbol table index.

Symbol table entry

data SymEnt c Source #

Symbol table entry.

Constructors

SymEnt 

Instances

Serializable SymEnt64 Source # 

Methods

put :: Serializer s => SymEnt64 -> s #

Serializable SymEnt32 Source # 

Methods

put :: Serializer s => SymEnt32 -> s #

SizedSerializable SymEnt64 Source # 

Methods

size :: Proxy * SymEnt64 -> Int #

SizedSerializable SymEnt32 Source # 

Methods

size :: Proxy * SymEnt32 -> Int #

Deserializable SymEnt64 Source # 

Methods

get :: Deserializer μ => μ SymEnt64 #

Deserializable SymEnt32 Source # 

Methods

get :: Deserializer μ => μ SymEnt32 #

IsFileClass c => Eq (SymEnt c) Source # 

Methods

(==) :: SymEnt c -> SymEnt c -> Bool #

(/=) :: SymEnt c -> SymEnt c -> Bool #

(Data c, IsFileClass c) => Data (SymEnt c) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SymEnt c -> c (SymEnt c) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (SymEnt c) #

toConstr :: SymEnt c -> Constr #

dataTypeOf :: SymEnt c -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (SymEnt c)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (SymEnt c)) #

gmapT :: (forall b. Data b => b -> b) -> SymEnt c -> SymEnt c #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SymEnt c -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SymEnt c -> r #

gmapQ :: (forall d. Data d => d -> u) -> SymEnt c -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> SymEnt c -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> SymEnt c -> m (SymEnt c) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SymEnt c -> m (SymEnt c) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SymEnt c -> m (SymEnt c) #

IsFileClass c => Read (SymEnt c) Source # 
IsFileClass c => Show (SymEnt c) Source # 

Methods

showsPrec :: Int -> SymEnt c -> ShowS #

show :: SymEnt c -> String #

showList :: [SymEnt c] -> ShowS #

type SymEnt32 = SymEnt Elf32 Source #

ELF32 symbol table entry.

type SymEnt64 = SymEnt Elf64 Source #

ELF64 symbol table entry.

zeroSymEnt :: IsFileClass c => SymEnt c Source #

Symbol table entry filled with zeros.

Relocation table

Relocation type

newtype RelType c Source #

Relocation type.

Constructors

RelType 

Fields

Instances

IsFileClass c => Bounded (RelType c) Source # 
IsFileClass c => Enum (RelType c) Source # 

Methods

succ :: RelType c -> RelType c #

pred :: RelType c -> RelType c #

toEnum :: Int -> RelType c #

fromEnum :: RelType c -> Int #

enumFrom :: RelType c -> [RelType c] #

enumFromThen :: RelType c -> RelType c -> [RelType c] #

enumFromTo :: RelType c -> RelType c -> [RelType c] #

enumFromThenTo :: RelType c -> RelType c -> RelType c -> [RelType c] #

IsFileClass c => Eq (RelType c) Source # 

Methods

(==) :: RelType c -> RelType c -> Bool #

(/=) :: RelType c -> RelType c -> Bool #

(Data c, IsFileClass c) => Data (RelType c) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RelType c -> c (RelType c) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RelType c) #

toConstr :: RelType c -> Constr #

dataTypeOf :: RelType c -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (RelType c)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RelType c)) #

gmapT :: (forall b. Data b => b -> b) -> RelType c -> RelType c #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RelType c -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RelType c -> r #

gmapQ :: (forall d. Data d => d -> u) -> RelType c -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RelType c -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RelType c -> m (RelType c) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RelType c -> m (RelType c) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RelType c -> m (RelType c) #

IsFileClass c => Ord (RelType c) Source # 

Methods

compare :: RelType c -> RelType c -> Ordering #

(<) :: RelType c -> RelType c -> Bool #

(<=) :: RelType c -> RelType c -> Bool #

(>) :: RelType c -> RelType c -> Bool #

(>=) :: RelType c -> RelType c -> Bool #

max :: RelType c -> RelType c -> RelType c #

min :: RelType c -> RelType c -> RelType c #

IsFileClass c => Read (RelType c) Source # 
IsFileClass c => Show (RelType c) Source # 

Methods

showsPrec :: Int -> RelType c -> ShowS #

show :: RelType c -> String #

showList :: [RelType c] -> ShowS #

IsFileClass c => Ix (RelType c) Source # 

Methods

range :: (RelType c, RelType c) -> [RelType c] #

index :: (RelType c, RelType c) -> RelType c -> Int #

unsafeIndex :: (RelType c, RelType c) -> RelType c -> Int

inRange :: (RelType c, RelType c) -> RelType c -> Bool #

rangeSize :: (RelType c, RelType c) -> Int #

unsafeRangeSize :: (RelType c, RelType c) -> Int

type RelType32 = RelType Elf32 Source #

ELF32 relocation type.

type RelType64 = RelType Elf64 Source #

ELF64 relocation type.

Relocation table entry

data RelEnt c Source #

Relocation table entry (REL).

Constructors

RelEnt 

Fields

Instances

Serializable RelEnt64 Source # 

Methods

put :: Serializer s => RelEnt64 -> s #

Serializable RelEnt32 Source # 

Methods

put :: Serializer s => RelEnt32 -> s #

SizedSerializable RelEnt64 Source # 

Methods

size :: Proxy * RelEnt64 -> Int #

SizedSerializable RelEnt32 Source # 

Methods

size :: Proxy * RelEnt32 -> Int #

Deserializable RelEnt64 Source # 

Methods

get :: Deserializer μ => μ RelEnt64 #

Deserializable RelEnt32 Source # 

Methods

get :: Deserializer μ => μ RelEnt32 #

IsFileClass c => Eq (RelEnt c) Source # 

Methods

(==) :: RelEnt c -> RelEnt c -> Bool #

(/=) :: RelEnt c -> RelEnt c -> Bool #

(Data c, IsFileClass c) => Data (RelEnt c) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RelEnt c -> c (RelEnt c) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RelEnt c) #

toConstr :: RelEnt c -> Constr #

dataTypeOf :: RelEnt c -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (RelEnt c)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RelEnt c)) #

gmapT :: (forall b. Data b => b -> b) -> RelEnt c -> RelEnt c #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RelEnt c -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RelEnt c -> r #

gmapQ :: (forall d. Data d => d -> u) -> RelEnt c -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RelEnt c -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RelEnt c -> m (RelEnt c) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RelEnt c -> m (RelEnt c) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RelEnt c -> m (RelEnt c) #

IsFileClass c => Read (RelEnt c) Source # 
IsFileClass c => Show (RelEnt c) Source # 

Methods

showsPrec :: Int -> RelEnt c -> ShowS #

show :: RelEnt c -> String #

showList :: [RelEnt c] -> ShowS #

type RelEnt32 = RelEnt Elf32 Source #

ELF32 relocation table entry (REL).

type RelEnt64 = RelEnt Elf64 Source #

ELF64 relocation table entry (REL).

data RelaEnt c Source #

Relocation table entry (RELA).

Constructors

RelaEnt 

Fields

Instances

Serializable RelaEnt64 Source # 

Methods

put :: Serializer s => RelaEnt64 -> s #

Serializable RelaEnt32 Source # 

Methods

put :: Serializer s => RelaEnt32 -> s #

SizedSerializable RelaEnt64 Source # 

Methods

size :: Proxy * RelaEnt64 -> Int #

SizedSerializable RelaEnt32 Source # 

Methods

size :: Proxy * RelaEnt32 -> Int #

Deserializable RelaEnt64 Source # 

Methods

get :: Deserializer μ => μ RelaEnt64 #

Deserializable RelaEnt32 Source # 

Methods

get :: Deserializer μ => μ RelaEnt32 #

IsFileClass c => Eq (RelaEnt c) Source # 

Methods

(==) :: RelaEnt c -> RelaEnt c -> Bool #

(/=) :: RelaEnt c -> RelaEnt c -> Bool #

(Data c, IsFileClass c) => Data (RelaEnt c) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> RelaEnt c -> c (RelaEnt c) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (RelaEnt c) #

toConstr :: RelaEnt c -> Constr #

dataTypeOf :: RelaEnt c -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (RelaEnt c)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (RelaEnt c)) #

gmapT :: (forall b. Data b => b -> b) -> RelaEnt c -> RelaEnt c #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> RelaEnt c -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> RelaEnt c -> r #

gmapQ :: (forall d. Data d => d -> u) -> RelaEnt c -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> RelaEnt c -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> RelaEnt c -> m (RelaEnt c) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> RelaEnt c -> m (RelaEnt c) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> RelaEnt c -> m (RelaEnt c) #

IsFileClass c => Read (RelaEnt c) Source # 
IsFileClass c => Show (RelaEnt c) Source # 

Methods

showsPrec :: Int -> RelaEnt c -> ShowS #

show :: RelaEnt c -> String #

showList :: [RelaEnt c] -> ShowS #

type RelaEnt32 = RelaEnt Elf32 Source #

ELF32 relocation table entry (RELA).

type RelaEnt64 = RelaEnt Elf64 Source #

ELF64 relocation table entry (RELA).