bytepatch-0.4.1: Patch byte-representable data in a bytestream
Safe HaskellSafe-Inferred
LanguageGHC2021

StreamPatch.Patch.Binary

Synopsis

Documentation

data Meta a Source #

Constructors

Meta 

Fields

Instances

Instances details
Foldable (Meta :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Methods

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

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

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

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

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

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

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

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

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

toList :: Meta a -> [a] #

null :: Meta a -> Bool #

length :: Meta a -> Int #

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

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

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

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

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

Traversable (Meta :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Methods

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

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

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

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

Functor (Meta :: TYPE LiftedRep -> Type) Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Methods

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

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

Generic (Meta a) Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Associated Types

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

Methods

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

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

Show (Meta a) Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Methods

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

show :: Meta a -> String #

showList :: [Meta a] -> ShowS #

Eq (Meta a) Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Methods

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

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

type Rep (Meta a) Source # 
Instance details

Defined in StreamPatch.Patch.Binary

type Rep (Meta a) = D1 ('MetaData "Meta" "StreamPatch.Patch.Binary" "bytepatch-0.4.1-inplace" 'False) (C1 ('MetaCons "Meta" 'PrefixI 'True) (S1 ('MetaSel ('Just "mNullTerminates") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural))))

data MetaPrep Source #

Constructors

MetaPrep 

Fields

  • mpMaxBytes :: Maybe Natural

    Maximum bytelength of binrepped data.

    Though binrepping is a safe operation, this is a useful sanity check in cases where you know the maximum space available.

    Note that this is only available for the patch data, not other meta data. (If you want that, you'll need to shove this field into the patch type.) itself. Probably not very useful.)

Instances

Instances details
Generic MetaPrep Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Associated Types

type Rep MetaPrep :: Type -> Type #

Methods

from :: MetaPrep -> Rep MetaPrep x #

to :: Rep MetaPrep x -> MetaPrep #

Show MetaPrep Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Eq MetaPrep Source # 
Instance details

Defined in StreamPatch.Patch.Binary

type Rep MetaPrep Source # 
Instance details

Defined in StreamPatch.Patch.Binary

type Rep MetaPrep = D1 ('MetaData "MetaPrep" "StreamPatch.Patch.Binary" "bytepatch-0.4.1-inplace" 'False) (C1 ('MetaCons "MetaPrep" 'PrefixI 'True) (S1 ('MetaSel ('Just "mpMaxBytes") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Maybe Natural))))

data Error a Source #

Constructors

ErrorBinRepOverlong BLenT BLenT a (Maybe ByteString)

If the value was serialized, it's given in the Maybe.

Instances

Instances details
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) #

Functor Error Source # 
Instance details

Defined in StreamPatch.Patch.Binary

Methods

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

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

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 #

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 #

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

Defined in StreamPatch.Patch.Binary

Methods

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

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

type Rep (Error a) Source # 
Instance details

Defined in StreamPatch.Patch.Binary

binRepify :: forall a s ss is r rs. (Put a, BLen a, Traversable (HFunctorList rs), r ~ Const MetaPrep, rs ~ RDelete r ss, RElem r ss (RIndex r ss), RSubset rs ss is) => Patch s ss a -> Either (Error a) (Patch s rs ByteString) Source #

binRepifyNull :: forall ec s r1 r2 ss rs is. (r1 ~ Meta, r2 ~ Meta ('ViaEq ec), rs ~ RDelete r1 ss, RElem r1 ss (RIndex r1 ss), RSubset rs ss is, RElem r2 rs (RIndex r2 rs), RecElem Rec r2 r2 rs rs (RIndex r2 rs)) => Patch s ss ByteString -> Patch s rs ByteString Source #

Treat the nulls field as a "this is how many extra nulls there are", and amend the compare meta for a patch by appending those nulls, and strip that stream-time bin meta.

Correct thing to do, but needs lots of changes elsewhere too. Dang.