summaryrefslogtreecommitdiff
path: root/haskell/Data/VCDIFF.hs
diff options
context:
space:
mode:
Diffstat (limited to 'haskell/Data/VCDIFF.hs')
-rw-r--r--haskell/Data/VCDIFF.hs54
1 files changed, 35 insertions, 19 deletions
diff --git a/haskell/Data/VCDIFF.hs b/haskell/Data/VCDIFF.hs
index 78f66ff..c48eb1a 100644
--- a/haskell/Data/VCDIFF.hs
+++ b/haskell/Data/VCDIFF.hs
@@ -11,23 +11,18 @@
11{-# LANGUAGE RankNTypes #-} 11{-# LANGUAGE RankNTypes #-}
12{-# LANGUAGE TypeFamilies #-} 12{-# LANGUAGE TypeFamilies #-}
13{-# LANGUAGE TypeOperators #-} 13{-# LANGUAGE TypeOperators #-}
14-- | 14-- | Create and apply binary diffs (in the 'VCDIFF' format) to lazy bytestrings.
15-- 15module Data.VCDIFF
16-- Create and apply binary diffs in the VCDIFF format. 16 ( VCDIFF
17-- 17 , encodeVCDIFF
18-- To create a diff: 18 , decodeVCDIFF
19-- 19 , Config(..)
20-- > diff = computeDiff defaultConfig source target 20 , defaultConfig
21-- 21 , Flags
22-- To apply a change to produce an updated version: 22 , pattern XD3_ADLER32
23-- 23 , Result(..)
24-- > target = applyPatch defaultConfig source diff 24 , computeDiff
25-- 25 , applyPatch) where
26-- Unlike typical text patches, context is ignored and
27-- there is no fuzz. This means the file you apply
28-- the patch to must have identical contents to the source
29-- used to create it.
30module Data.VCDIFF where
31 26
32import Control.Monad 27import Control.Monad
33import Control.Monad.Primitive 28import Control.Monad.Primitive
@@ -211,21 +206,37 @@ encode_input :: PrimMonad m => Stream m -> m ErrorCode
211encode_input stream = 206encode_input stream =
212 unsafeIOToPrim $ xd3_encode_input (streamArrayPtr $ streamArray stream) 207 unsafeIOToPrim $ xd3_encode_input (streamArrayPtr $ streamArray stream)
213 208
214-- RFC 3284 209-- | A binary diff (or patch) in the VCDIFF format documented by RFC 3284.
215newtype VCDIFF = VCDIFF L.ByteString 210--
211-- When used as a patch, context is ignored and there is no fuzz. This means
212-- the file you apply the patch to must have identical contents to the source
213-- used to create it. /WARNING:/ This wont be checked unless 'XD3_ADLER32' flag
214-- was specified to 'computeDiff'.
215newtype VCDIFF = VCDIFF { encodeVCDIFF :: L.ByteString }
216 deriving Show 216 deriving Show
217 217
218decodeVCDIFF :: L.ByteString -> Either String VCDIFF
219decodeVCDIFF = Right . VCDIFF
220
221
218chunksOf :: Usize_t -> L.ByteString -> [B.ByteString] 222chunksOf :: Usize_t -> L.ByteString -> [B.ByteString]
219chunksOf len bs | L.null bs = [] 223chunksOf len bs | L.null bs = []
220 | otherwise = let (b,bs') = L.splitAt (fromIntegral len) bs 224 | otherwise = let (b,bs') = L.splitAt (fromIntegral len) bs
221 in L.toStrict b : chunksOf len bs' 225 in L.toStrict b : chunksOf len bs'
222 226
227-- | Compute a binary diff. For most options, use 'defaultConfig', but you may
228-- want to set 'flags' to 'XD3_ADLER32' to add checksumming safety to the
229-- patch, and a larger 'chunk_size' may yield greater compression.
223computeDiff :: Config -> L.ByteString -> L.ByteString -> Result VCDIFF 230computeDiff :: Config -> L.ByteString -> L.ByteString -> Result VCDIFF
224computeDiff cfg source patched = fmap VCDIFF $ xdeltaPure encode_input cfg source patched 231computeDiff cfg source patched = fmap VCDIFF $ xdeltaPure encode_input cfg source patched
225 232
233-- | Apply a patch. It is okay to use 'defaultConfig' for most options, but
234-- you may want to specify an alternative'chunk_size' for streaming.
226applyPatch :: Config -> L.ByteString -> VCDIFF -> Result L.ByteString 235applyPatch :: Config -> L.ByteString -> VCDIFF -> Result L.ByteString
227applyPatch cfg source (VCDIFF delta) = xdeltaPure decode_input cfg source delta 236applyPatch cfg source (VCDIFF delta) = xdeltaPure decode_input cfg source delta
228 237
238-- | The result of a computation that may fail. On failure, the 'result' field
239-- is truncated or invalid.
229data Result x = Result 240data Result x = Result
230 { result :: x -- ^ A possibly invalid result. To consume a lazy stream with fusion, avoid 241 { result :: x -- ^ A possibly invalid result. To consume a lazy stream with fusion, avoid
231 -- evaluating 'resultError' until this field is fully processed. 242 -- evaluating 'resultError' until this field is fully processed.
@@ -257,6 +268,11 @@ xdeltaPure codec cfg source input =
257 } 268 }
258 in runST $ xdelta x codec ds 269 in runST $ xdelta x codec ds
259 270
271-- | Sensible defaults. All of these configuration items are passed on to the
272-- xdelta algorithm except 'chunk_size' which is used by 'computeDiff' and
273-- 'applyPatch' to divide the input into chunks (see 'chunksOf').
274--
275-- Consider enabling flags = 'XD3_ADLER32' for added safety.
260defaultConfig :: Config 276defaultConfig :: Config
261defaultConfig = Config 277defaultConfig = Config
262 { winsize = XD3_DEFAULT_WINSIZE 278 { winsize = XD3_DEFAULT_WINSIZE