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

StreamPatch.Patch

Description

Core patch type: patches, seeks, metadata container.

This library is based around patches to streams i.e. containers indexed by the natural numbers (or integers, depending on your view). As such, we restrict what a seek can look like. Parts of the codebase could be generalized to work over any seek kind, so you could e.g. write a text patcher that uses line and column positions to seek through the data. But you can't transform line and column to byte position, at least not without parsing the file. So it would need a lot of thought and careful design to generalize in that direction.

Synopsis

Documentation

data Patch s fs a Source #

A single patch on a stream of a.

Constructors

Patch 

Fields

Instances

Instances details
Foldable (HFunctorList fs) => Foldable (Patch s fs) Source # 
Instance details

Defined in StreamPatch.Patch

Methods

fold :: Monoid m => Patch s fs m -> m #

foldMap :: Monoid m => (a -> m) -> Patch s fs a -> m #

foldMap' :: Monoid m => (a -> m) -> Patch s fs a -> m #

foldr :: (a -> b -> b) -> b -> Patch s fs a -> b #

foldr' :: (a -> b -> b) -> b -> Patch s fs a -> b #

foldl :: (b -> a -> b) -> b -> Patch s fs a -> b #

foldl' :: (b -> a -> b) -> b -> Patch s fs a -> b #

foldr1 :: (a -> a -> a) -> Patch s fs a -> a #

foldl1 :: (a -> a -> a) -> Patch s fs a -> a #

toList :: Patch s fs a -> [a] #

null :: Patch s fs a -> Bool #

length :: Patch s fs a -> Int #

elem :: Eq a => a -> Patch s fs a -> Bool #

maximum :: Ord a => Patch s fs a -> a #

minimum :: Ord a => Patch s fs a -> a #

sum :: Num a => Patch s fs a -> a #

product :: Num a => Patch s fs a -> a #

Traversable (HFunctorList fs) => Traversable (Patch s fs) Source # 
Instance details

Defined in StreamPatch.Patch

Methods

traverse :: Applicative f => (a -> f b) -> Patch s fs a -> f (Patch s fs b) #

sequenceA :: Applicative f => Patch s fs (f a) -> f (Patch s fs a) #

mapM :: Monad m => (a -> m b) -> Patch s fs a -> m (Patch s fs b) #

sequence :: Monad m => Patch s fs (m a) -> m (Patch s fs a) #

Functor (HFunctorList fs) => Functor (Patch s fs) Source # 
Instance details

Defined in StreamPatch.Patch

Methods

fmap :: (a -> b) -> Patch s fs a -> Patch s fs b #

(<$) :: a -> Patch s fs b -> Patch s fs a #

(FromJSON a, FromJSON s, FromJSON (HFunctorList fs a)) => FromJSON (Patch s fs a) Source # 
Instance details

Defined in StreamPatch.Patch

Methods

parseJSON :: Value -> Parser (Patch s fs a) #

parseJSONList :: Value -> Parser [Patch s fs a] #

(ToJSON a, ToJSON s, ToJSON (HFunctorList fs a)) => ToJSON (Patch s fs a) Source # 
Instance details

Defined in StreamPatch.Patch

Methods

toJSON :: Patch s fs a -> Value #

toEncoding :: Patch s fs a -> Encoding #

toJSONList :: [Patch s fs a] -> Value #

toEncodingList :: [Patch s fs a] -> Encoding #

(Data a, Data s, Data (HFunctorList fs a), Typeable fs) => Data (Patch s fs a) Source # 
Instance details

Defined in StreamPatch.Patch

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Patch s fs a -> c (Patch s fs a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Patch s fs a) #

toConstr :: Patch s fs a -> Constr #

dataTypeOf :: Patch s fs a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Patch s fs a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Patch s fs a)) #

gmapT :: (forall b. Data b => b -> b) -> Patch s fs a -> Patch s fs a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Patch s fs a -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Patch s fs a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Patch s fs a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Patch s fs a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Patch s fs a -> m (Patch s fs a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Patch s fs a -> m (Patch s fs a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Patch s fs a -> m (Patch s fs a) #

Generic (Patch s fs a) Source # 
Instance details

Defined in StreamPatch.Patch

Associated Types

type Rep (Patch s fs a) :: Type -> Type #

Methods

from :: Patch s fs a -> Rep (Patch s fs a) x #

to :: Rep (Patch s fs a) x -> Patch s fs a #

(Show a, Show s, Show (HFunctorList fs a)) => Show (Patch s fs a) Source # 
Instance details

Defined in StreamPatch.Patch

Methods

showsPrec :: Int -> Patch s fs a -> ShowS #

show :: Patch s fs a -> String #

showList :: [Patch s fs a] -> ShowS #

(Eq a, Eq s, Eq (HFunctorList fs a)) => Eq (Patch s fs a) Source # 
Instance details

Defined in StreamPatch.Patch

Methods

(==) :: Patch s fs a -> Patch s fs a -> Bool #

(/=) :: Patch s fs a -> Patch s fs a -> Bool #

type Rep (Patch s fs a) Source # 
Instance details

Defined in StreamPatch.Patch

type Rep (Patch s fs a) = D1 ('MetaData "Patch" "StreamPatch.Patch" "bytepatch-0.4.1-inplace" 'False) (C1 ('MetaCons "Patch" 'PrefixI 'True) (S1 ('MetaSel ('Just "patchData") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: (S1 ('MetaSel ('Just "patchSeek") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 s) :*: S1 ('MetaSel ('Just "patchMeta") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (HFunctorList fs a)))))