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

StreamPatch.Patch.Align

Synopsis

Documentation

data Meta s Source #

Constructors

Meta 

Fields

Instances

Instances details
Eq (SeekRep s) => Eq (Meta s) Source # 
Instance details

Defined in StreamPatch.Patch.Align

Methods

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

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

Show (SeekRep s) => Show (Meta s) Source # 
Instance details

Defined in StreamPatch.Patch.Align

Methods

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

show :: Meta s -> String #

showList :: [Meta s] -> ShowS #

Generic (Meta s) Source # 
Instance details

Defined in StreamPatch.Patch.Align

Associated Types

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

Methods

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

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

type Rep (Meta s) Source # 
Instance details

Defined in StreamPatch.Patch.Align

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

data Error s Source #

Instances

Instances details
Eq (SeekRep s) => Eq (Error s) Source # 
Instance details

Defined in StreamPatch.Patch.Align

Methods

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

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

Show (SeekRep s) => Show (Error s) Source # 
Instance details

Defined in StreamPatch.Patch.Align

Methods

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

show :: Error s -> String #

showList :: [Error s] -> ShowS #

Generic (Error s) Source # 
Instance details

Defined in StreamPatch.Patch.Align

Associated Types

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

Methods

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

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

type Rep (Error s) Source # 
Instance details

Defined in StreamPatch.Patch.Align

type Rep (Error s) = D1 ('MetaData "Error" "StreamPatch.Patch.Align" "bytepatch-0.3.1-inplace" 'False) (C1 ('MetaCons "ErrorSeekBelow0" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SeekRep 'RelSeek))) :+: C1 ('MetaCons "ErrorDoesntMatchExpected" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SeekRep s)) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (SeekRep s))))

align :: forall s a ss rs is i r. (SeekRep s ~ Natural, r ~ Const (Meta s), rs ~ RDelete r ss, RElem r ss i, RSubset rs ss is) => SeekRep 'RelSeek -> Patch 'RelSeek ss a -> Either (Error s) (Patch s rs a) Source #

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