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

StreamPatch.Patch.Binary

Synopsis

Documentation

data Meta Source #

Constructors

Meta 

Fields

Instances

Instances details
Eq Meta Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Methods

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

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

Show Meta Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Methods

showsPrec :: Int -> Meta -> ShowS #

show :: Meta -> String #

showList :: [Meta] -> ShowS #

Generic Meta Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Associated Types

type Rep Meta :: Type -> Type #

Methods

from :: Meta -> Rep Meta x #

to :: Rep Meta x -> Meta #

type Rep Meta Source # 
Instance details

Defined in StreamPatch.Patch.Binary

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

data MetaStream a Source #

Constructors

MetaStream 

Fields

Instances

Instances details
Functor MetaStream Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Methods

fmap :: (a -> b) -> MetaStream a -> MetaStream b #

(<$) :: a -> MetaStream b -> MetaStream a #

Foldable MetaStream Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Methods

fold :: Monoid m => MetaStream m -> m #

foldMap :: Monoid m => (a -> m) -> MetaStream a -> m #

foldMap' :: Monoid m => (a -> m) -> MetaStream a -> m #

foldr :: (a -> b -> b) -> b -> MetaStream a -> b #

foldr' :: (a -> b -> b) -> b -> MetaStream a -> b #

foldl :: (b -> a -> b) -> b -> MetaStream a -> b #

foldl' :: (b -> a -> b) -> b -> MetaStream a -> b #

foldr1 :: (a -> a -> a) -> MetaStream a -> a #

foldl1 :: (a -> a -> a) -> MetaStream a -> a #

toList :: MetaStream a -> [a] #

null :: MetaStream a -> Bool #

length :: MetaStream a -> Int #

elem :: Eq a => a -> MetaStream a -> Bool #

maximum :: Ord a => MetaStream a -> a #

minimum :: Ord a => MetaStream a -> a #

sum :: Num a => MetaStream a -> a #

product :: Num a => MetaStream a -> a #

Traversable MetaStream Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Methods

traverse :: Applicative f => (a -> f b) -> MetaStream a -> f (MetaStream b) #

sequenceA :: Applicative f => MetaStream (f a) -> f (MetaStream a) #

mapM :: Monad m => (a -> m b) -> MetaStream a -> m (MetaStream b) #

sequence :: Monad m => MetaStream (m a) -> m (MetaStream a) #

Eq a => Eq (MetaStream a) Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Methods

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

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

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

Defined in StreamPatch.Patch.Binary

Generic (MetaStream a) Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Associated Types

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

Methods

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

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

type Rep (MetaStream a) Source # 
Instance details

Defined in StreamPatch.Patch.Binary

type Rep (MetaStream a) = D1 ('MetaData "MetaStream" "StreamPatch.Patch.Binary" "bytepatch-0.3.1-inplace" 'False) (C1 ('MetaCons "MetaStream" 'PrefixI 'True) (S1 ('MetaSel ('Just "msNullTerminates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe (SeekRep 'FwdSeek))) :*: S1 ('MetaSel ('Just "msExpected") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe a))))

data Cfg Source #

Constructors

Cfg 

Fields

  • 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 StreamPatch.Patch.Binary

Methods

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

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

Show Cfg Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Methods

showsPrec :: Int -> Cfg -> ShowS #

show :: Cfg -> String #

showList :: [Cfg] -> ShowS #

Generic Cfg Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Associated Types

type Rep Cfg :: Type -> Type #

Methods

from :: Cfg -> Rep Cfg x #

to :: Rep Cfg x -> Cfg #

type Rep Cfg Source # 
Instance details

Defined in StreamPatch.Patch.Binary

type Rep Cfg = D1 ('MetaData "Cfg" "StreamPatch.Patch.Binary" "bytepatch-0.3.1-inplace" 'False) (C1 ('MetaCons "Cfg" 'PrefixI 'True) (S1 ('MetaSel ('Just "cfgAllowPartialExpected") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))

data Error a Source #

Instances

Instances details
Functor Error Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Methods

fmap :: (a -> b) -> Error a -> Error b #

(<$) :: a -> Error b -> Error a #

Foldable Error Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Methods

fold :: Monoid m => Error m -> m #

foldMap :: Monoid m => (a -> m) -> Error a -> m #

foldMap' :: Monoid m => (a -> m) -> Error a -> m #

foldr :: (a -> b -> b) -> b -> Error a -> b #

foldr' :: (a -> b -> b) -> b -> Error a -> b #

foldl :: (b -> a -> b) -> b -> Error a -> b #

foldl' :: (b -> a -> b) -> b -> Error a -> b #

foldr1 :: (a -> a -> a) -> Error a -> a #

foldl1 :: (a -> a -> a) -> Error a -> a #

toList :: Error a -> [a] #

null :: Error a -> Bool #

length :: Error a -> Int #

elem :: Eq a => a -> Error a -> Bool #

maximum :: Ord a => Error a -> a #

minimum :: Ord a => Error a -> a #

sum :: Num a => Error a -> a #

product :: Num a => Error a -> a #

Traversable Error Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Methods

traverse :: Applicative f => (a -> f b) -> Error a -> f (Error b) #

sequenceA :: Applicative f => Error (f a) -> f (Error a) #

mapM :: Monad m => (a -> m b) -> Error a -> m (Error b) #

sequence :: Monad m => Error (m a) -> m (Error a) #

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

Defined in StreamPatch.Patch.Binary

Methods

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

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

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

Defined in StreamPatch.Patch.Binary

Methods

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

show :: Error a -> String #

showList :: [Error a] -> ShowS #

Generic (Error a) Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Associated Types

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

Methods

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

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

type Rep (Error a) Source # 
Instance details

Defined in StreamPatch.Patch.Binary

patchBinRep :: forall a s ss rs is i r. (BinRep a, Traversable (FunctorRec rs), r ~ Const Meta, rs ~ RDelete r ss, RElem r ss i, RSubset rs ss is) => Patch s ss a -> Either (Error a) (Patch s rs ByteString) Source #

class BinRep a where Source #

Type has a binary representation for using in patchscripts.

Patchscripts are parsed parameterized over the type to edit. That type needs to become a bytestring for eventual patch application. We're forced into newtypes and typeclasses by Aeson already, so this just enables us to define some important patch generation behaviour in one place. Similarly to Aeson, if you require custom behaviour for existing types (e.g. length-prefixed strings instead of C-style null terminated), define a newtype over it.

Some values may not have valid patch representations, for example if you're patching a 1-byte length-prefixed string and your string is too long (>255 encoded bytes). Thus, toPatchRep is failable.

Instances

Instances details
BinRep String Source #

String is the same but goes the long way round, through Text.

Instance details

Defined in StreamPatch.Patch.Binary

BinRep ByteString Source #

Bytestrings are copied as-is.

Instance details

Defined in StreamPatch.Patch.Binary

BinRep Text Source #

Text is converted to UTF-8 bytes and null-terminated.

Instance details

Defined in StreamPatch.Patch.Binary

BinRep HexByteString Source # 
Instance details

Defined in BytePatch.HexByteString

KnownNat n => BinRep (PascalText n) Source # 
Instance details

Defined in StreamPatch.Patch.Binary.PascalText