
-- This program takes patch filenames as arguments and splits the patch -- files up on a hunk-by-hunk basis. I have found this useful for Linux -- kernel development, and perhaps others might find it useful in -- similar contexts where patches are the primary method of communication. module Main where import System import List main = getArgs >>= mapM_ splatterHunkFile splatterHunkFile file = mapM_ (\(f,ss) -> writeFile f (unlines ss)) . zip (map (((reverse . takeWhile (/= '/') . reverse $ file)++).("-"++).show) [1..]) . splatterHunks =<< readFile file splatterHunks ss = map (map unlines) $ zipWith (\s -> map (s:)) (map head . (splitList "diff") $ lines ss) (map (splitList "@@") . (splitList "diff") $ lines ss) splitList prefix ss = map ($ss) $ zipWith (\m n -> (if n >= 0 then take (n - m) else id) . drop m) (map fst . filter (\(n,s) -> isPrefixOf prefix s) $ zip [0..] ss) (tail (map fst . filter (\(n,s) -> isPrefixOf prefix s) $ zip [0..] ss) ++ [-1])

On Sun, Nov 17, 2002 at 03:20:46AM -0800, William Lee Irwin III wrote:
-- This program takes patch filenames as arguments and splits the patch -- files up on a hunk-by-hunk basis. I have found this useful for Linux -- kernel development, and perhaps others might find it useful in -- similar contexts where patches are the primary method of communication.
Managed to shrink it a bit and get it a wee bit better-behaved to boot. module Main where import System import List main = getArgs >>= mapM_ (\file -> sequence_ . zipWith writeFile (map (((reverse . takeWhile (/= '/') . reverse $ file)++).("-"++).show) [1..]) . splatterHunks =<< readFile file) splatterHunks = map unlines . concatMap (\s -> map ((++) (take 3 s)) (splitList "@@" s)) . splitList "diff" . lines splitList prefix ss = [[s | (k, s) <- ss', m <= k, n > k || n <= 0] | (m,n) <- let ss'' = [j | (j,s) <- ss', prefix `isPrefixOf` s] in zip ss'' (tail ss'' ++ [-1])] where ss' = zip [0..] ss
participants (1)
-
William Lee Irwin III