
Okay, I have looked up KMP and implemented it. Seems to work -- my first use of QuickCheck, too. It's slower than Bulat's and Tomasz' for Branimir's test :-(, but really fast for my test. Undoubtedly, one can still tune it. Here's the code: module KMP where import Data.Array searchReplace :: String -> String -> String -> String searchReplace "" _ str = str searchReplace src@(c:cs) dst str = process 0 str "" where len = length src pat = listArray (0,len-1) src bord = array (0,len) $ (0,-1):(1,0):[(i+1,boun i (bord!i)) | i <- [1 .. len-1]] boun i j | j < 0 = 0 | pat!i == pat!j = j+1 | otherwise = boun i (bord!j) getBord s n | m < 1 = m | s == pat!m = m | otherwise = getBord s m where m = bord!n process n str _ | n >= len = dst ++ process 0 str "" process _ "" mat = reverse mat process 0 (s:st) _ | s == c = process 1 st [s] | otherwise = s:process 0 st "" process n str@(s:st) mat | s == pat!n = process (n+1) st (s:mat) | otherwise = let j = getBord s n (ret,skip) = splitAt j mat in if j < 0 then reverse mat ++ process 0 str "" else reverse skip ++ process j str ret Cheers, Daniel