bytepatch-0.4.0: Patch byte-representable data in a bytestream
Safe HaskellSafe-Inferred
LanguageHaskell2010

StreamPatch.Patch.Align

Synopsis

Documentation

data Meta st Source #

Constructors

Meta 

Fields

  • mExpected :: Maybe st

    Absolute stream offset for edit. Used for checking against actual offset.

Instances

Instances details
Generic (Meta st) Source # 
Instance details

Defined in StreamPatch.Patch.Align

Associated Types

type Rep (Meta st) :: Type -> Type #

Methods

from :: Meta st -> Rep (Meta st) x #

to :: Rep (Meta st) x -> Meta st #

Show st => Show (Meta st) Source # 
Instance details

Defined in StreamPatch.Patch.Align

Methods

showsPrec :: Int -> Meta st -> ShowS #

show :: Meta st -> String #

showList :: [Meta st] -> ShowS #

Eq st => Eq (Meta st) Source # 
Instance details

Defined in StreamPatch.Patch.Align

Methods

(==) :: Meta st -> Meta st -> Bool #

(/=) :: Meta st -> Meta st -> Bool #

type Rep (Meta st) Source # 
Instance details

Defined in StreamPatch.Patch.Align

type Rep (Meta st) = D1 ('MetaData "Meta" "StreamPatch.Patch.Align" "bytepatch-0.4.0-inplace" 'False) (C1 ('MetaCons "Meta" 'PrefixI 'True) (S1 ('MetaSel ('Just "mExpected") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe st))))

data Error st Source #

Instances

Instances details
Generic (Error st) Source # 
Instance details

Defined in StreamPatch.Patch.Align

Associated Types

type Rep (Error st) :: Type -> Type #

Methods

from :: Error st -> Rep (Error st) x #

to :: Rep (Error st) x -> Error st #

Show st => Show (Error st) Source # 
Instance details

Defined in StreamPatch.Patch.Align

Methods

showsPrec :: Int -> Error st -> ShowS #

show :: Error st -> String #

showList :: [Error st] -> ShowS #

Eq st => Eq (Error st) Source # 
Instance details

Defined in StreamPatch.Patch.Align

Methods

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

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

type Rep (Error st) Source # 
Instance details

Defined in StreamPatch.Patch.Align

type Rep (Error st) = D1 ('MetaData "Error" "StreamPatch.Patch.Align" "bytepatch-0.4.0-inplace" 'False) (C1 ('MetaCons "ErrorAlignedToNegative" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Integer)) :+: C1 ('MetaCons "ErrorDoesntMatchExpected" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 st) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 st)))

align :: forall sf st a ss is r rs. (Integral sf, Num st, Eq st, r ~ Const (Meta st), rs ~ RDelete r ss, RElem r ss (RIndex r ss), RSubset rs ss is) => Integer -> Patch sf ss a -> Either (Error st) (Patch st rs a) Source #

Attempt to align the given patch to 0 using the given base.

The resulting seek is guaranteed to be non-negative, so you may use natural-like types safely.

TODO Complicated.