summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJoe Crayne <joe@jerkface.net>2018-10-28 20:06:51 -0400
committerJoe Crayne <joe@jerkface.net>2018-10-28 20:06:51 -0400
commitb344e040b82cfbdb8b82bebd397f18661d7f88c7 (patch)
treee6ccc916d52317bb3b8b9eacf20ccf0647feeadd
parentaebdc1ce3ed5b53ba69dd3aa0f37d1ffefbf5c7d (diff)
Some documentation.
-rw-r--r--haskell/Data/VCDIFF.hs54
-rw-r--r--haskell/examples/testdiff.hs30
2 files changed, 60 insertions, 24 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
diff --git a/haskell/examples/testdiff.hs b/haskell/examples/testdiff.hs
index 7e20dc5..3f6e3e2 100644
--- a/haskell/examples/testdiff.hs
+++ b/haskell/examples/testdiff.hs
@@ -10,22 +10,42 @@ source = "It could be said that Joe was here. I don't know what to do about it."
10patched :: L.ByteString 10patched :: L.ByteString
11patched = "It could be said that Joe, the magnificent, was here. I don't know what to do about it." 11patched = "It could be said that Joe, the magnificent, was here. I don't know what to do about it."
12 12
13source2 :: L.ByteString
14source2 = "It could be said that Joe was absolutely here. I don't know what to do about it."
15
13delta :: Result VCDIFF 16delta :: Result VCDIFF
14delta = computeDiff defaultConfig source patched 17delta = computeDiff defaultConfig source patched
15 18
19delta2 :: Result VCDIFF
20delta2 = computeDiff defaultConfig { flags = XD3_ADLER32 } source patched
21
16main = do 22main = do
23 putStrLn "source"
17 mapM_ putStrLn $ xxd2 0 (L.toStrict source) 24 mapM_ putStrLn $ xxd2 0 (L.toStrict source)
18 putStrLn "" 25 putStrLn ""
26 putStrLn "target"
19 mapM_ putStrLn $ xxd2 0 (L.toStrict patched) 27 mapM_ putStrLn $ xxd2 0 (L.toStrict patched)
20 putStrLn "" 28 putStrLn ""
29 case delta2 of
30 Result δ me -> do
31 let d = encodeVCDIFF δ
32 putStrLn "diff(XD3_ADLER32)"
33 mapM_ putStrLn $ xxd2 0 (L.toStrict d)
34 print me
35 putStrLn ""
36 let Result patched' pe = applyPatch defaultConfig source2 δ
37 putStrLn "patched(XD3_ADLER32)"
38 mapM_ putStrLn $ xxd2 0 (L.toStrict patched') -- $ L.take 48 patched')
39 print pe
40 putStrLn ""
21 case delta of 41 case delta of
22 Result δ@(VCDIFF d) me -> do 42 Result δ me -> do
23 -- mapM_ (mapM_ putStrLn . xxd2 0) (chunksOf 16 d) 43 let d = encodeVCDIFF δ
44 putStrLn "diff(default)"
24 mapM_ putStrLn $ xxd2 0 (L.toStrict d) 45 mapM_ putStrLn $ xxd2 0 (L.toStrict d)
25 print me 46 print me
26 putStrLn "" 47 putStrLn ""
27 let Result patched' pe = applyPatch defaultConfig source δ 48 putStrLn "patched(default)"
49 let Result patched' pe = applyPatch defaultConfig source2 δ
28 mapM_ putStrLn $ xxd2 0 (L.toStrict patched') -- $ L.take 48 patched') 50 mapM_ putStrLn $ xxd2 0 (L.toStrict patched') -- $ L.take 48 patched')
29 print pe 51 print pe
30 print ("source",source)
31 print ("patched",patched)