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

BytePatch.Linear.Patch

Description

Low-level patchscript processing and application.

Patchscripts are applied as a list of (skip x, write in-place y) commands. An offset-based format is much simpler to use, however. This module processes such offset patchscripts into a "linear" patchscript, and provides a stream patching algorithm that can be applied to any forward-seeking byte stream.

Some core types are parameterized over the stream type/patch content. This enables writing patches in any form (e.g. UTF-8 text), which are then processed into an applicable patch by transforming edits into a concrete binary representation (e.g. null-terminated UTF-8 bytestring). See TODO module for more.

Synopsis

Patch interface

class Monad m => MonadFwdByteStream m where Source #

Methods

readahead :: Natural -> m Bytes Source #

Read a number of bytes without advancing the cursor.

advance :: Natural -> m () Source #

Advance cursor without reading.

overwrite :: Bytes -> m () Source #

Insert bytes into the stream at the cursor position, overwriting existing bytes.

Instances

Instances details
MonadIO m => MonadFwdByteStream (ReaderT Handle m) Source # 
Instance details

Defined in BytePatch.Linear.Patch

Methods

readahead :: Natural -> ReaderT Handle m Bytes Source #

advance :: Natural -> ReaderT Handle m () Source #

overwrite :: Bytes -> ReaderT Handle m () Source #

data Cfg Source #

Patch time config.

Constructors

Cfg 

Fields

  • cfgWarnIfLikelyReprocessing :: Bool

    If we determine that we're repatching an already-patched stream, continue with a warning instead of failing.

  • cfgAllowPartialExpected :: Bool

    If enabled, allow partial expected bytes checking. If disabled, then even if the expected bytes are a prefix of the actual, fail.

Instances

Instances details
Eq Cfg Source # 
Instance details

Defined in BytePatch.Linear.Patch

Methods

(==) :: Cfg -> Cfg -> Bool

(/=) :: Cfg -> Cfg -> Bool

Show Cfg Source # 
Instance details

Defined in BytePatch.Linear.Patch

Methods

showsPrec :: Int -> Cfg -> ShowS

show :: Cfg -> String

showList :: [Cfg] -> ShowS

data Error Source #

Errors encountered during patch time.

Instances

Instances details
Eq Error Source # 
Instance details

Defined in BytePatch.Linear.Patch

Methods

(==) :: Error -> Error -> Bool

(/=) :: Error -> Error -> Bool

Show Error Source # 
Instance details

Defined in BytePatch.Linear.Patch

Methods

showsPrec :: Int -> Error -> ShowS

show :: Error -> String

showList :: [Error] -> ShowS

Prepared patchers

patchPure :: Cfg -> [Patch 'FwdSeek Bytes] -> ByteString -> Either Error ByteString Source #

Attempt to apply a patchscript to a ByteString.

General patcher

patch :: MonadFwdByteStream m => Cfg -> [Patch 'FwdSeek Bytes] -> m (Maybe Error) Source #