bytepatch-0.2.0: Patch byte-representable data in a bytestream.
Safe HaskellNone
LanguageHaskell2010

BytePatch.Pretty

Description

Convenience interface to enable defining edits at offsets with some optional safety checks.

Synopsis

Core types

data MultiPatches a Source #

A list of patches sharing a configuration, each applied at a list of offsets, abstracted over patch type.

Constructors

MultiPatches 

Fields

  • mpsBaseOffset :: Maybe Int

    The base offset from which all offsets are located. Subtracted from each offset value to obtain the actual offset. Any offset located before the base offset (x where x < base) is discarded as erroneous.

    This feature enables us to allow negative offsets. For example, say you set the base offset to -10. This is equivalent to stating that every offset in the list is to be shifted +10 bytes. Thus, all offsets x where x >= -10 are now valid.

    The original rationale behind this feature was to ease assembly patches on ELFs. Decompilers focus on virtual addresses, and apparently (in my experience) don't like to divulge physical file offsets. However, we can recover the physical offset of any virtual address via the following steps:

    1. subtract the containing ELF segment's virtual address
    2. add the containing ELF segment's physical offset

    So we can prepare a base offset elf_vaddr - elf_phys_offset, which we can subtract from any virtual address inside that segment to retrieve its related byte offset in the ELF file. Thus, you need do that calculation manually once for every segment you patch, then you can use your decompiler's virtual addresses!

    You can even specify absolute offsets, which are compared to the calculated actual offsets. So you get the best of both worlds!

    Absolute offsets are only used for asserting correctness of calculated actual offsets. If you want to mix absolute and base-relative offsets... don't. I'm loath to support that, because I believe it would serve only to confuse the patch file interface. Instead, group patches into absolute (base offset = 0) and base-relative lists.

  • mpsPatches :: [MultiPatch a]
     

Instances

Instances details
Eq a => Eq (MultiPatches a) Source # 
Instance details

Defined in BytePatch.Pretty

Show a => Show (MultiPatches a) Source # 
Instance details

Defined in BytePatch.Pretty

Generic (MultiPatches a) Source # 
Instance details

Defined in BytePatch.Pretty

Associated Types

type Rep (MultiPatches a) :: Type -> Type #

Methods

from :: MultiPatches a -> Rep (MultiPatches a) x #

to :: Rep (MultiPatches a) x -> MultiPatches a #

ToJSON a => ToJSON (MultiPatches a) Source # 
Instance details

Defined in BytePatch.JSON

FromJSON a => FromJSON (MultiPatches a) Source # 
Instance details

Defined in BytePatch.JSON

type Rep (MultiPatches a) Source # 
Instance details

Defined in BytePatch.Pretty

type Rep (MultiPatches a) = D1 ('MetaData "MultiPatches" "BytePatch.Pretty" "bytepatch-0.2.0-2TXM0rJut3lJpkgCCGgU2G" 'False) (C1 ('MetaCons "MultiPatches" 'PrefixI 'True) (S1 ('MetaSel ('Just "mpsBaseOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "mpsPatches") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [MultiPatch a])))

data MultiPatch a Source #

A single patch applied at a list of offsets, parameterized by patch type.

Constructors

MultiPatch 

Fields

Instances

Instances details
Eq a => Eq (MultiPatch a) Source # 
Instance details

Defined in BytePatch.Pretty

Methods

(==) :: MultiPatch a -> MultiPatch a -> Bool #

(/=) :: MultiPatch a -> MultiPatch a -> Bool #

Show a => Show (MultiPatch a) Source # 
Instance details

Defined in BytePatch.Pretty

Generic (MultiPatch a) Source # 
Instance details

Defined in BytePatch.Pretty

Associated Types

type Rep (MultiPatch a) :: Type -> Type #

Methods

from :: MultiPatch a -> Rep (MultiPatch a) x #

to :: Rep (MultiPatch a) x -> MultiPatch a #

ToJSON a => ToJSON (MultiPatch a) Source # 
Instance details

Defined in BytePatch.JSON

FromJSON a => FromJSON (MultiPatch a) Source # 
Instance details

Defined in BytePatch.JSON

type Rep (MultiPatch a) Source # 
Instance details

Defined in BytePatch.Pretty

type Rep (MultiPatch a) = D1 ('MetaData "MultiPatch" "BytePatch.Pretty" "bytepatch-0.2.0-2TXM0rJut3lJpkgCCGgU2G" 'False) (C1 ('MetaCons "MultiPatch" 'PrefixI 'True) (S1 ('MetaSel ('Just "mpContents") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "mpOffsets") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [Offset a])))

data Offset a Source #

An offset in a stream, with metadata about it to use when preparing the patch and at patch time.

Constructors

Offset 

Fields

  • oOffset :: Int

    Stream offset to patch at.

  • oAbsoluteOffset :: Maybe Int

    Absolute stream offset to patch at. Compared with actual offset (calculated from offset and base offset).

  • oMaxLength :: Maybe Int

    Maximum bytestring length allowed to patch in at this offset. TODO: use single range/span instead (default 0->x, also allow y->x)

  • oPatchMeta :: Maybe (OverwriteMeta a)

    Patch-time info for the overwrite at this offset.

    Named "patch meta" instead of the more correct "overwrite meta" for more friendly JSON field naming. We wrap it in a Maybe for similar reasons, plus it means the default can be inserted later on.

Instances

Instances details
Eq a => Eq (Offset a) Source # 
Instance details

Defined in BytePatch.Pretty

Methods

(==) :: Offset a -> Offset a -> Bool #

(/=) :: Offset a -> Offset a -> Bool #

Show a => Show (Offset a) Source # 
Instance details

Defined in BytePatch.Pretty

Methods

showsPrec :: Int -> Offset a -> ShowS #

show :: Offset a -> String #

showList :: [Offset a] -> ShowS #

Generic (Offset a) Source # 
Instance details

Defined in BytePatch.Pretty

Associated Types

type Rep (Offset a) :: Type -> Type #

Methods

from :: Offset a -> Rep (Offset a) x #

to :: Rep (Offset a) x -> Offset a #

ToJSON a => ToJSON (Offset a) Source # 
Instance details

Defined in BytePatch.JSON

FromJSON a => FromJSON (Offset a) Source # 
Instance details

Defined in BytePatch.JSON

type Rep (Offset a) Source # 
Instance details

Defined in BytePatch.Pretty

type Rep (Offset a) = D1 ('MetaData "Offset" "BytePatch.Pretty" "bytepatch-0.2.0-2TXM0rJut3lJpkgCCGgU2G" 'False) (C1 ('MetaCons "Offset" 'PrefixI 'True) ((S1 ('MetaSel ('Just "oOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "oAbsoluteOffset") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int))) :*: (S1 ('MetaSel ('Just "oMaxLength") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Int)) :*: S1 ('MetaSel ('Just "oPatchMeta") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (OverwriteMeta a))))))

Convenience functions

normalizeSimple :: PatchRep a => [MultiPatches a] -> Maybe [Patch Bytes] Source #

Normalize a set of MultiPatches, discarding everything on error.

Low-level interface

listAlgebraConcatEtc :: [(a, [(b, [c])])] -> ([b], [(c, a)]) Source #