Differences in optimisiation with interactive and compiled mode

It seems that compiled programs run better then interactive ones. Following program with GHC works with pretty good performance in comparison to C++ one with similar but non recursive algorithm and beats it in memory consumtion. It only takes about 2mb of ram somehow when running compiled. I'm really amased. But in interactive mode both GHC and Hugs fail due heap exhaustion and running takes ages.Please can someone explain why? I intent to use only compiled Haskell anyway so GHC satisfies. Greetings, Bane. program performs search replace on a String module Main where import IO main = do hSetBuffering stdout LineBuffering let sr = "search" rp = "replace" str= " able search sea baker search charlie \"" out = searchr sr rp (take (1000000*(length str)) $ infinite str) out1 = searchr sr rp (take (1000001*(length str)) $ infinite str) putStrLn $ "Working:" ++ sr ++ " " ++ rp ++ " " ++ str putStrLn $ (show (out == out1)) ++ "\n" ++ "\nDone\n" {- search replace " able search baker search charlie " -} ------------------------------------------------------------------------------- infinite xs = xs ++ infinite xs searchr :: String->String->String -> String searchr [] _ xs = xs searchr _ [] xs = xs searchr _ _ [] = [] searchr sr rp xs | fst fnd = rp ++ searchr sr rp (snd $ snd fnd) | otherwise = (reverse $ fst $ snd fnd) ++ searchr sr rp (snd $ snd fnd) where fnd = searchr' sr xs "" searchr' :: String->String->String -> (Bool,(String,String)) searchr' (sr:srs) xs fndSoFar = searchr'' (sr:srs) xs fndSoFar sr searchr'' :: String->String->String->Char -> (Bool,(String,String)) searchr'' [] xs fnd _ = (True,(fnd,xs)) searchr'' _ [] fnd _ = (False,(fnd,[])) searchr'' (sr:srs) (x:xs) fndSoFar s | sr == x = searchr'' srs xs xxs s | otherwise = (False,searchr''' s xs xxs) -- (False,(xxs,xs)) where xxs = x:fndSoFar searchr''' :: Char->String->String -> (String,String) searchr''' sr [] fndSoFar = (fndSoFar,[]) searchr''' sr (x:xs) fndSoFar | sr /= x = searchr''' sr xs (x:fndSoFar) | otherwise = (fndSoFar,x:xs) ------------------------------------------------------------------------------- _________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

GHCi does things with optimisations off. Note the line on startup which says:
Compiling Main ( search.hs, interpreted )
You'll have better luck if you compile the code with optimisations and
keep the .o files around when running the program in ghci -- it will
notice the compiled copies and load those instead. You'll see
something like:
Skipping Main ( search.hs, search.o )
Also note that your 'infinite' function is in the prelude. It's called 'cycle'.
- Cale
On 08/12/05, Branimir Maksimovic
It seems that compiled programs run better then interactive ones. Following program with GHC works with pretty good performance in comparison to C++ one with similar but non recursive algorithm and beats it in memory consumtion. It only takes about 2mb of ram somehow when running compiled. I'm really amased. But in interactive mode both GHC and Hugs fail due heap exhaustion and running takes ages.Please can someone explain why? I intent to use only compiled Haskell anyway so GHC satisfies.
Greetings, Bane.
program performs search replace on a String
module Main where import IO main = do hSetBuffering stdout LineBuffering let sr = "search" rp = "replace" str= " able search sea baker search charlie \"" out = searchr sr rp (take (1000000*(length str)) $ infinite str) out1 = searchr sr rp (take (1000001*(length str)) $ infinite str) putStrLn $ "Working:" ++ sr ++ " " ++ rp ++ " " ++ str putStrLn $ (show (out == out1)) ++ "\n" ++ "\nDone\n" {- search replace " able search baker search charlie " -}
------------------------------------------------------------------------------- infinite xs = xs ++ infinite xs
searchr :: String->String->String -> String searchr [] _ xs = xs searchr _ [] xs = xs searchr _ _ [] = [] searchr sr rp xs | fst fnd = rp ++ searchr sr rp (snd $ snd fnd) | otherwise = (reverse $ fst $ snd fnd) ++ searchr sr rp (snd $ snd fnd) where fnd = searchr' sr xs ""
searchr' :: String->String->String -> (Bool,(String,String)) searchr' (sr:srs) xs fndSoFar = searchr'' (sr:srs) xs fndSoFar sr
searchr'' :: String->String->String->Char -> (Bool,(String,String)) searchr'' [] xs fnd _ = (True,(fnd,xs)) searchr'' _ [] fnd _ = (False,(fnd,[])) searchr'' (sr:srs) (x:xs) fndSoFar s | sr == x = searchr'' srs xs xxs s | otherwise = (False,searchr''' s xs xxs) -- (False,(xxs,xs)) where xxs = x:fndSoFar
searchr''' :: Char->String->String -> (String,String) searchr''' sr [] fndSoFar = (fndSoFar,[]) searchr''' sr (x:xs) fndSoFar | sr /= x = searchr''' sr xs (x:fndSoFar) | otherwise = (fndSoFar,x:xs) -------------------------------------------------------------------------------
_________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

From: Cale Gibbard
To: Branimir Maksimovic CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive and compiled mode Date: Thu, 8 Dec 2005 09:26:11 -0500 GHCi does things with optimisations off. Note the line on startup which says: Compiling Main ( search.hs, interpreted ) You'll have better luck if you compile the code with optimisations and keep the .o files around when running the program in ghci -- it will notice the compiled copies and load those instead. You'll see something like: Skipping Main ( search.hs, search.o )
This is good thing, thanks for noticing me about it. But something else bothers me. Perhaps I've missed some flag for ghci, but for stand alone executable I get low memory consumption (about 2mb), no matter optimised or not, except that non optimised version runs about three times slower. When running from ghci and invoking main function interactivelly, I get more then 400mb of ram used with optimisations and just 20mb without. So there must be something different in run time system as standalone executable use just 2mb of ram which is excellent performance, but in ghci non optimised version performs better and actually consume much less memory then optimised one.
Also note that your 'infinite' function is in the prelude. It's called 'cycle'.
Thanks. I will use it from now on. Greetings, Bane.
- Cale
On 08/12/05, Branimir Maksimovic
wrote: It seems that compiled programs run better then interactive ones. Following program with GHC works with pretty good performance in comparison to C++ one with similar but non recursive algorithm and beats it in memory consumtion. It only takes about 2mb of ram somehow when running compiled. I'm really amased. But in interactive mode both GHC and Hugs fail due heap exhaustion and running takes ages.Please can someone explain why? I intent to use only compiled Haskell anyway so GHC satisfies.
Greetings, Bane.
program performs search replace on a String
module Main where import IO main = do hSetBuffering stdout LineBuffering let sr = "search" rp = "replace" str= " able search sea baker search charlie \"" out = searchr sr rp (take (1000000*(length str)) $ infinite str) out1 = searchr sr rp (take (1000001*(length str)) $ infinite str) putStrLn $ "Working:" ++ sr ++ " " ++ rp ++ " " ++ str putStrLn $ (show (out == out1)) ++ "\n" ++ "\nDone\n" {- search replace " able search baker search charlie " -}
-------------------------------------------------------------------------------
infinite xs = xs ++ infinite xs
searchr :: String->String->String -> String searchr [] _ xs = xs searchr _ [] xs = xs searchr _ _ [] = [] searchr sr rp xs | fst fnd = rp ++ searchr sr rp (snd $ snd fnd) | otherwise = (reverse $ fst $ snd fnd) ++ searchr sr rp (snd $ snd fnd) where fnd = searchr' sr xs ""
searchr' :: String->String->String -> (Bool,(String,String)) searchr' (sr:srs) xs fndSoFar = searchr'' (sr:srs) xs fndSoFar sr
searchr'' :: String->String->String->Char -> (Bool,(String,String)) searchr'' [] xs fnd _ = (True,(fnd,xs)) searchr'' _ [] fnd _ = (False,(fnd,[])) searchr'' (sr:srs) (x:xs) fndSoFar s | sr == x = searchr'' srs xs xxs s | otherwise = (False,searchr''' s xs xxs) -- (False,(xxs,xs)) where xxs = x:fndSoFar
searchr''' :: Char->String->String -> (String,String) searchr''' sr [] fndSoFar = (fndSoFar,[]) searchr''' sr (x:xs) fndSoFar | sr /= x = searchr''' sr xs (x:fndSoFar) | otherwise = (fndSoFar,x:xs)
-------------------------------------------------------------------------------
_________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

On Thu, 8 Dec 2005, Branimir Maksimovic wrote:
program performs search replace on a String
http://www.haskell.org/pipermail/haskell-cafe/2005-April/009692.html

From: Henning Thielemann
To: Branimir Maksimovic CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive and compiled mode Date: Thu, 8 Dec 2005 18:38:45 +0100 (MET) On Thu, 8 Dec 2005, Branimir Maksimovic wrote:
program performs search replace on a String
http://www.haskell.org/pipermail/haskell-cafe/2005-April/009692.html
This is nice and ellegant but example search replace program runs more then 50% faster with my implementation. Greetings, Bane. _________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

On Thu, 8 Dec 2005, Branimir Maksimovic wrote:
From: Henning Thielemann
To: Branimir Maksimovic CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive and compiled mode Date: Thu, 8 Dec 2005 18:38:45 +0100 (MET) On Thu, 8 Dec 2005, Branimir Maksimovic wrote:
program performs search replace on a String
http://www.haskell.org/pipermail/haskell-cafe/2005-April/009692.html
This is nice and ellegant but example search replace program runs more then 50% faster with my implementation.
Is this intended: *SearchReplace> searchr "ha" "lo" "hha" "hha" ?

From: Henning Thielemann
To: Branimir Maksimovic CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive and compiled mo Date: Fri, 9 Dec 2005 09:23:53 +0100 (MET) On Thu, 8 Dec 2005, Branimir Maksimovic wrote:
From: Henning Thielemann
To: Branimir Maksimovic CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive and compiled mode Date: Thu, 8 Dec 2005 18:38:45 +0100 (MET) On Thu, 8 Dec 2005, Branimir Maksimovic wrote:
program performs search replace on a String
http://www.haskell.org/pipermail/haskell-cafe/2005-April/009692.html
This is nice and ellegant but example search replace program runs more then 50% faster with my implementation.
Is this intended:
*SearchReplace> searchr "ha" "lo" "hha" "hha"
?
thanks, this is a bug. I over optimised it :) that should be : searchr'' (sr:srs) (x:xs) fndSoFar s | sr == x = searchr'' srs xs (x:fndSoFar) s | otherwise = (False,searchr''' s (x:xs) fndSoFar) instead of searchr'' (sr:srs) (x:xs) fndSoFar s | sr == x = searchr'' srs xs xxs s | otherwise = (False,searchr''' s xs xxs) where xxs = x:fndSoFar Just to say my algorithm takes some optimisation opportunities. For example if "search" "replace" " able search baker search charlie " then it will run much faster then if " able sssssssssssssssssearch baker search charlie " Worst case is repetitive first mathing character, but than it is fast as normal implementation. Greetings, Bane. _________________________________________________________________ Is your PC infected? Get a FREE online computer virus scan from McAfee® Security. http://clinic.mcafee.com/clinic/ibuy/campaign.asp?cid=3963

Hello Branimir, Friday, December 09, 2005, 12:24:16 PM, you wrote: BM> Just to say my algorithm takes some optimisation opportunities. look at http://haskell.org/hawiki/RunTimeCompilation -- Best regards, Bulat mailto:bulatz@HotPOP.com

Still doesn't work, though: *Main> searchr "hahal" "jupp" "hahahalala" "hahahalala" The problem is that the string to replace may contain a repeated pattern and the pattern that begins the actual occurence might be consumed before a failure is detected. And is *Main> searchr "bla" "" "remove bla bla" "remove bla bla" really intended? Cheers, Daniel Am Freitag, 9. Dezember 2005 10:24 schrieb Branimir Maksimovic:
From: Henning Thielemann
To: Branimir Maksimovic
CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive and compiled mo Date: Fri, 9 Dec 2005 09:23:53 +0100 (MET) On Thu, 8 Dec 2005, Branimir Maksimovic wrote:
From: Henning Thielemann
To: Branimir Maksimovic CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive and compiled mode Date: Thu, 8 Dec 2005 18:38:45 +0100 (MET) On Thu, 8 Dec 2005, Branimir Maksimovic wrote:
program performs search replace on a String
http://www.haskell.org/pipermail/haskell-cafe/2005-April/009692.html
This is nice and ellegant but example search replace program runs more then 50% faster with my implementation.
Is this intended:
*SearchReplace> searchr "ha" "lo" "hha" "hha"
?
thanks, this is a bug. I over optimised it :) that should be : searchr'' (sr:srs) (x:xs) fndSoFar s | sr == x = searchr'' srs xs (x:fndSoFar) s
| otherwise = (False,searchr''' s | (x:xs)
fndSoFar)
instead of searchr'' (sr:srs) (x:xs) fndSoFar s | sr == x = searchr'' srs xs xxs s
| otherwise = (False,searchr''' s xs
xxs) where xxs = x:fndSoFar
Just to say my algorithm takes some optimisation opportunities. For example if "search" "replace" " able search baker search charlie " then it will run much faster then if " able sssssssssssssssssearch baker search charlie " Worst case is repetitive first mathing character, but than it is fast as normal implementation.
Greetings, Bane.

From: Daniel Fischer
To: "Branimir Maksimovic" CC: Haskell-Cafe@haskell.org Subject: Re: Differences in optimisiation with interactive and compiled mo Date: Fri, 9 Dec 2005 23:27:00 +0100 Still doesn't work, though:
*Main> searchr "hahal" "jupp" "hahahalala" "hahahalala"
The problem is that the string to replace may contain a repeated pattern and the pattern that begins the actual occurence might be consumed before a failure is detected.
Yes, I've corrected it. Now it is just 25% faster and that is only with -O2 flag. Here is whole thing, I hope there are no more bugs left :) : module Main where import IO import List main = do hSetBuffering stdout LineBuffering let sr = "seasearch" rp = "replace" str= " able seaseaseasearch baker ssseasearch charlie " out = searchr sr rp (take (1000000*(length str)) $ cycle str) out1 = replace sr rp (take (1000000*(length str)) $ cycle str) putStrLn $ "Working:" ++ sr ++ " " ++ rp ++ " " ++ str putStrLn $ (show (out == out1)) ++ "\nDone\n" {- search replace " able search baker search charlie " -} ------------------------------------------------------------------------------- --infinite xs = xs ++ infinite xs searchr :: String->String->String -> String searchr [] _ xs = xs --searchr _ [] xs = xs searchr _ _ [] = [] searchr sr rp xs | fst fnd = rp ++ searchr sr rp (snd $ snd fnd) | otherwise = (reverse $ fst $ snd fnd) ++ searchr sr rp (snd $ snd fnd) where fnd = searchr' sr xs "" searchr' :: String->String->String -> (Bool,(String,String)) searchr' (sr:srs) xs fndSoFar = searchr'' (sr:srs) xs fndSoFar (False,False,"") sr searchr'' :: String->String->String->(Bool,Bool,String)->Char -> (Bool,(String,String)) searchr'' [] xs fnd _ _ = (True,(fnd,xs)) searchr'' _ [] fnd _ _ = (False,(fnd,[])) searchr'' (sr:srs) (x:xs) fndSoFar (cnt,f,rollBack) s | sr == x = if cnt && (f || s == x) then searchr'' srs xs fndSoFar (True,True,x:rollBack) s else searchr'' srs xs (x:fndSoFar) (True,f,rollBack) s | otherwise = if not f then (False,searchr''' s (x:xs) fndSoFar) else (False,(fndSoFar,(reverse rollBack)++(x:xs))) searchr''' :: Char->String->String -> (String,String) searchr''' sr [] fndSoFar = (fndSoFar,[]) searchr''' sr (x:xs) fndSoFar | sr/=x = searchr''' sr xs (x:fndSoFar) | otherwise = (fndSoFar,x:xs) ------------------------------------------------------------------------------- replace :: forall a. (Eq a) => [a] -> [a] -> [a] -> [a] replace src dst = foldr (\x xs -> let y=x:xs in if isPrefixOf src y then dst ++ drop (length src) y else y) []
And is *Main> searchr "bla" "" "remove bla bla" "remove bla bla" really intended?
Originaly yes, but I've changed that now. Greetings, Bane.
Cheers, Daniel
From: Henning Thielemann
To: Branimir Maksimovic
CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive and compiled mo Date: Fri, 9 Dec 2005 09:23:53 +0100 (MET) On Thu, 8 Dec 2005, Branimir Maksimovic wrote:
From: Henning Thielemann
To: Branimir Maksimovic CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive and compiled mode Date: Thu, 8 Dec 2005 18:38:45 +0100 (MET) On Thu, 8 Dec 2005, Branimir Maksimovic wrote:
program performs search replace on a String
http://www.haskell.org/pipermail/haskell-cafe/2005-April/009692.html
This is nice and ellegant but example search replace program runs more then 50% faster with my implementation.
Is this intended:
*SearchReplace> searchr "ha" "lo" "hha" "hha"
?
thanks, this is a bug. I over optimised it :) that should be : searchr'' (sr:srs) (x:xs) fndSoFar s | sr == x = searchr'' srs xs (x:fndSoFar) s
| otherwise = (False,searchr''' s | (x:xs)
fndSoFar)
instead of searchr'' (sr:srs) (x:xs) fndSoFar s | sr == x = searchr'' srs xs xxs s
| otherwise = (False,searchr''' s xs
xxs) where xxs = x:fndSoFar
Just to say my algorithm takes some optimisation opportunities. For example if "search" "replace" " able search baker search charlie "
Am Freitag, 9. Dezember 2005 10:24 schrieb Branimir Maksimovic: then
it will run much faster then if " able sssssssssssssssssearch baker search charlie " Worst case is repetitive first mathing character, but than it is fast as normal implementation.
Greetings, Bane.
_________________________________________________________________ Don't just search. Find. Check out the new MSN Search! http://search.msn.click-url.com/go/onm00200636ave/direct/01/

Am Samstag, 10. Dezember 2005 02:51 schrieben Sie:
From: Daniel Fischer
To: "Branimir Maksimovic"
CC: Haskell-Cafe@haskell.org Subject: Re: Differences in optimisiation with interactive and compiled mo Date: Fri, 9 Dec 2005 23:27:00 +0100 Still doesn't work, though:
*Main> searchr "hahal" "jupp" "hahahalala" "hahahalala"
The problem is that the string to replace may contain a repeated pattern and the pattern that begins the actual occurence might be consumed before a failure is detected.
Yes, I've corrected it. Now it is just 25% faster and that is only with -O2 flag. Here is whole thing, I hope there are no more bugs left :) :
None that sprang to my eyes. However, on my machine, yours is not faster than Lemmih's. Now, using the new Strings, I get the following times: -O2 -O1 no opt Lemmih's: 38.9 sec 38.9 sec 76.7 sec Yours : 40.1 sec 41.5 sec 131.1 sec Mine : 32.9 sec 33.1 sec 82.8 sec. However, there's a problem with Lemmih's replace: *Main> searchr "ababcab" "###" "ababcababcabab" "###abcab" *Main> replace "ababcab" "###" "ababcababcabab" "ababc###ab" due to the fact that Lemmih's version scans the input from right to left (that's easily changed by a few reverses, though -- but costly for long inputs), more serious is Prelude Main> replace "ja" "aja" "jjjjjjja" "ajajajajajajaja". The fastest -- and nicely simple above -- that I could come up with is replace :: String -> String -> String -> String replace _ _ "" = "" replace "" _ str = str replace src dst inp = process inp where n = length src process "" = "" process st@(c:cs) | src `isPrefixOf` st = dst ++ process (drop n st) | otherwise = c:process cs It's roughly 10% faster than my other version on "seasearch" ... and if you try it on main2 :: IO () main2 = let src = replicate 1000 'r' dst = " # " str = replicate 999 'r' ++ 'c': replicate 1000 'r' out = replace src dst $ concat $ replicate 500 str out1 = replace src dst $ concat $ replicate 501 str in do putStrLn $ "Working very long" putStrLn $ show (out == out1) ++ "\nDone" you'll see a real difference. I'm not sure, why your algorithm pays a so much higher penalty, though. Maybe, it'll be faster if you make searchr' &c local functions? I'll try. Cheers, Daniel

From: Daniel Fischer
To: "Branimir Maksimovic" CC: Haskell-Cafe@haskell.org Subject: Substring replacements (was: Differences in optimisiation ...) Date: Sat, 10 Dec 2005 22:56:10 +0100 and if you try it on
main2 :: IO () main2 = let src = replicate 1000 'r' dst = " # " str = replicate 999 'r' ++ 'c': replicate 1000 'r' out = replace src dst $ concat $ replicate 500 str out1 = replace src dst $ concat $ replicate 501 str in do putStrLn $ "Working very long" putStrLn $ show (out == out1) ++ "\nDone"
you'll see a real difference. I'm not sure, why your algorithm pays a so much higher penalty, though. Maybe, it'll be faster if you make searchr' &c local functions? I'll try.
Well, this is on my machine with your setup and -O2 flag: $ time replace.exe Working very long False Done real 0m31.828s user 0m0.015s sys 0m0.000s bmaxa@MAXA ~/tutorial $ time searchr.exe Working very long False Done real 0m37.531s user 0m0.015s sys 0m0.000s bmaxa@MAXA ~/tutorial $ time srchrep.exe Working very long False Done real 0m18.047s user 0m0.015s sys 0m0.015s bmaxa@MAXA ~/tutorial $ time replace1.exe Working very long False Done real 0m12.531s user 0m0.015s sys 0m0.000s replace1 is Bulat's newest algorithm. It is really incredibly fastest with this setup. Greetings, Bane. _________________________________________________________________ FREE pop-up blocking with the new MSN Toolbar - get it now! http://toolbar.msn.click-url.com/go/onm00200415ave/direct/01/

Hello Branimir, Sunday, December 11, 2005, 4:09:00 AM, you wrote: BM> replace1 is Bulat's newest algorithm. It is really incredibly fastest with BM> this setup. to be honest, it is combination of 4 lines from Tomasz's algorithm and 3 lines of mine :) -- Best regards, Bulat mailto:bulatz@HotPOP.com

After seeing your test, I've implemented full KMP algorithm, which is blazingly fast with your test. It is slower in mine test due excessive temporaries I guess, but perhaps you can help me to make it better as I'm just Haskell newbie. You can see that by my code :0) Especially I'm clumsy with passing parameters around. main :: IO () main =let src = replicate 1000 'r' dst = " # " str = replicate 999 'r' ++ 'c': replicate 1000 'r' out = searchReplace src dst $ concat $ replicate 500 str out1 = searchReplace src dst $ concat $ replicate 501 str in do putStrLn $ "Working very long" putStrLn $ show (out == out1) ++ "\nDone" ------------------------------------------------------------------------------- searchReplace :: String->String->String -> String searchReplace sr rp xs = searchr sr rp xs "" searchr :: String->String->String->String -> String searchr [] _ xs _ = xs searchr _ _ [] _ = [] searchr sr rp xs rollBack | fst $ fst fnd = rp ++ searchr sr rp (snd $ snd $ fst fnd) (snd fnd) | otherwise = reverse ((fst $ snd $ fst $ fnd) ++ rollBack) ++ searchr sr rp (snd $ snd $ fst fnd) (snd fnd) where fnd = searchr' (drop (length rollBack) sr) xs "" searchr' :: String->String->String -> ((Bool,(String,String)),String) searchr' (sr:srs) xs fndSoFar = searchr'' (sr:srs) xs fndSoFar (False,False,"") sr searchr'' :: String->String->String->(Bool,Bool,String)->Char -> ((Bool,(String,String)),String) searchr'' [] xs fnd _ _ = ((True,(fnd,xs)),"") searchr'' _ [] fnd _ _ = ((False,(fnd,[])),"") searchr'' (sr:srs) (x:xs) fndSoFar (cnt,f,rollBack) s | sr == x = if cnt && (f || s == x) then searchr'' srs xs fndSoFar (True,True,x:rollBack) s else searchr'' srs xs (x:fndSoFar) (True,False,"") s | otherwise = if not f then ((False,searchr''' s (x:xs) fndSoFar),"") else ((False,(fndSoFar,x:xs)),rollBack) searchr''' :: Char->String->String -> (String,String) searchr''' sr [] fndSoFar = (fndSoFar,[]) searchr''' sr (x:xs) fndSoFar | sr/=x = searchr''' sr xs (x:fndSoFar) | otherwise = (fndSoFar,x:xs) ------------------------------------------------------------------------------- Optimiser works extremilly well with this version in combination with your test: $ ghc -fglasgow-exts -O2 searchr.hs --make -o searchr.exe Chasing modules from: searchr.hs Compiling Main ( searchr.hs, searchr.o ) Linking ... bmaxa@MAXA ~/tutorial $ time searchr.exe Working very long False Done real 0m0.250s user 0m0.031s sys 0m0.000s Wow, just 0.25 seconds! No c++ program can approach near that! Perhaps I have bug somewhere but I've compared results with yours searchrep and seems same. Greetings, Bane.
From: Daniel Fischer
To: "Branimir Maksimovic" CC: Haskell-Cafe@haskell.org Subject: Substring replacements (was: Differences in optimisiation ...) Date: Sat, 10 Dec 2005 22:56:10 +0100 From: Daniel Fischer
To: "Branimir Maksimovic"
CC: Haskell-Cafe@haskell.org Subject: Re: Differences in optimisiation with interactive and compiled mo Date: Fri, 9 Dec 2005 23:27:00 +0100 Still doesn't work, though:
*Main> searchr "hahal" "jupp" "hahahalala" "hahahalala"
The problem is that the string to replace may contain a repeated
Am Samstag, 10. Dezember 2005 02:51 schrieben Sie: pattern
and the pattern that begins the actual occurence might be consumed before a failure is detected.
Yes, I've corrected it. Now it is just 25% faster and that is only with -O2 flag. Here is whole thing, I hope there are no more bugs left :) :
None that sprang to my eyes. However, on my machine, yours is not faster than Lemmih's. Now, using the new Strings, I get the following times: -O2 -O1 no opt Lemmih's: 38.9 sec 38.9 sec 76.7 sec Yours : 40.1 sec 41.5 sec 131.1 sec Mine : 32.9 sec 33.1 sec 82.8 sec.
However, there's a problem with Lemmih's replace:
*Main> searchr "ababcab" "###" "ababcababcabab" "###abcab" *Main> replace "ababcab" "###" "ababcababcabab" "ababc###ab"
due to the fact that Lemmih's version scans the input from right to left (that's easily changed by a few reverses, though -- but costly for long inputs), more serious is
Prelude Main> replace "ja" "aja" "jjjjjjja" "ajajajajajajaja".
The fastest -- and nicely simple above -- that I could come up with is
replace :: String -> String -> String -> String replace _ _ "" = "" replace "" _ str = str replace src dst inp = process inp where n = length src process "" = "" process st@(c:cs) | src `isPrefixOf` st = dst ++ process (drop n st) | otherwise = c:process cs
It's roughly 10% faster than my other version on "seasearch" ... and if you try it on
main2 :: IO () main2 = let src = replicate 1000 'r' dst = " # " str = replicate 999 'r' ++ 'c': replicate 1000 'r' out = replace src dst $ concat $ replicate 500 str out1 = replace src dst $ concat $ replicate 501 str in do putStrLn $ "Working very long" putStrLn $ show (out == out1) ++ "\nDone"
you'll see a real difference. I'm not sure, why your algorithm pays a so much higher penalty, though. Maybe, it'll be faster if you make searchr' &c local functions? I'll try.
Cheers, Daniel
_________________________________________________________________ FREE pop-up blocking with the new MSN Toolbar - get it now! http://toolbar.msn.click-url.com/go/onm00200415ave/direct/01/

I've found one remaining bug, and this is corrected version. Now it is fastest with your test (still 0.25 seconds), but undoubtly slowest with mine:0) But I crafted this test to be really rigorous to mine implementation. Lot of replaces, repated patterns and so. In real world situtaion it will perform much better, I hope. so here it is: ------------------------------------------------------------------------------- main :: IO () main =let src = replicate 1000 'r' dst = " # " str = replicate 999 'r' ++ 'c': replicate 1000 'r' out = searchReplace src dst $ concat $ replicate 500 str out1 = searchReplace src dst $ concat $ replicate 500 str in do putStrLn $ "Working very long" putStrLn $ show (out == out1) ++ "\nDone" ------------------------------------------------------------------------------- searchReplace :: String->String->String -> String searchReplace sr rp xs = searchr sr rp xs "" where searchr :: String->String->String->String -> String searchr [] _ xs _ = xs searchr _ _ [] _ = [] searchr sr rp xs rollBack | fst $ fst $ fnd = rp ++ searchr sr rp (snd $ snd $ fst $ fnd ) ( snd fnd ) | otherwise = reverse ((fst $ snd $ fst $ fnd ) ++ rollBack) ++ searchr sr rp (snd $ snd $ fst $ fnd) ( snd fnd) where fnd = searchr' (drop (length rollBack) sr) xs "" searchr' :: String->String->String -> ((Bool,(String,String)),String) searchr' (sr:srs) xs fndSoFar = searchr'' (sr:srs) xs fndSoFar (False,False,"") sr searchr'' :: String->String->String->(Bool,Bool,String)->Char -> ((Bool,(String,String)),String) searchr'' [] xs fnd _ _ = ((True,(fnd,xs)),"") searchr'' _ [] fnd (_,_,rollBack) _ = ((False,(fnd,[])),rollBack) searchr'' (sr:srs) (x:xs) fndSoFar (cnt,f,rollBack) s | sr == x = if cnt && (f || s == x) then searchr'' srs xs fndSoFar (True,True,x:rollBack) s else searchr'' srs xs (x:fndSoFar) (True,False,"") s | otherwise = if not f then if s == x then ((False,(fndSoFar,x:xs)),"") else ((False,searchr''' s xs (x:fndSoFar)),"") else if s == x && getFst rollBack == s then ((False,(fndSoFar, xs)),x:rollBack) else ((False,(fndSoFar,x:xs)),rollBack) searchr''' :: Char->String->String -> (String,String) searchr''' sr [] fndSoFar = (fndSoFar,[]) searchr''' sr (x:xs) fndSoFar -- | sr/=x = searchr''' sr xs (x:fndSoFar) | otherwise = (fndSoFar,x:xs) getFst (a:as) = a; -------------------------------------------------------------------------------
From: "Branimir Maksimovic"
To: daniel.is.fischer@web.de CC: Haskell-Cafe@haskell.org Subject: [Haskell-cafe] RE: Substring replacements (was: Differences inoptimisiation ...) Date: Sun, 11 Dec 2005 02:19:22 +0000 After seeing your test, I've implemented full KMP algorithm, which is blazingly fast with your test. It is slower in mine test due excessive temporaries I guess, but perhaps you can help me to make it better as I'm just Haskell newbie. You can see that by my code :0) Especially I'm clumsy with passing parameters around.
main :: IO () main =let src = replicate 1000 'r' dst = " # " str = replicate 999 'r' ++ 'c': replicate 1000 'r' out = searchReplace src dst $ concat $ replicate 500 str out1 = searchReplace src dst $ concat $ replicate 501 str in do putStrLn $ "Working very long" putStrLn $ show (out == out1) ++ "\nDone" ------------------------------------------------------------------------------- searchReplace :: String->String->String -> String searchReplace sr rp xs = searchr sr rp xs ""
searchr :: String->String->String->String -> String searchr [] _ xs _ = xs searchr _ _ [] _ = [] searchr sr rp xs rollBack | fst $ fst fnd = rp ++ searchr sr rp (snd $ snd $ fst fnd) (snd fnd) | otherwise = reverse ((fst $ snd $ fst $ fnd) ++ rollBack) ++ searchr sr rp (snd $ snd $ fst fnd) (snd fnd) where fnd = searchr' (drop (length rollBack) sr) xs ""
searchr' :: String->String->String -> ((Bool,(String,String)),String) searchr' (sr:srs) xs fndSoFar = searchr'' (sr:srs) xs fndSoFar (False,False,"") sr
searchr'' :: String->String->String->(Bool,Bool,String)->Char -> ((Bool,(String,String)),String) searchr'' [] xs fnd _ _ = ((True,(fnd,xs)),"") searchr'' _ [] fnd _ _ = ((False,(fnd,[])),"") searchr'' (sr:srs) (x:xs) fndSoFar (cnt,f,rollBack) s | sr == x = if cnt && (f || s == x) then searchr'' srs xs fndSoFar (True,True,x:rollBack) s else searchr'' srs xs (x:fndSoFar) (True,False,"") s | otherwise = if not f then ((False,searchr''' s (x:xs) fndSoFar),"") else ((False,(fndSoFar,x:xs)),rollBack)
searchr''' :: Char->String->String -> (String,String) searchr''' sr [] fndSoFar = (fndSoFar,[]) searchr''' sr (x:xs) fndSoFar | sr/=x = searchr''' sr xs (x:fndSoFar) | otherwise = (fndSoFar,x:xs) -------------------------------------------------------------------------------
Optimiser works extremilly well with this version in combination with your test: $ ghc -fglasgow-exts -O2 searchr.hs --make -o searchr.exe Chasing modules from: searchr.hs Compiling Main ( searchr.hs, searchr.o ) Linking ...
bmaxa@MAXA ~/tutorial $ time searchr.exe Working very long False Done
real 0m0.250s user 0m0.031s sys 0m0.000s
Wow, just 0.25 seconds! No c++ program can approach near that!
Perhaps I have bug somewhere but I've compared results with yours searchrep and seems same.
Greetings, Bane.
From: Daniel Fischer
To: "Branimir Maksimovic" CC: Haskell-Cafe@haskell.org Subject: Substring replacements (was: Differences in optimisiation ...) Date: Sat, 10 Dec 2005 22:56:10 +0100 From: Daniel Fischer
To: "Branimir Maksimovic"
CC: Haskell-Cafe@haskell.org Subject: Re: Differences in optimisiation with interactive and compiled mo Date: Fri, 9 Dec 2005 23:27:00 +0100 Still doesn't work, though:
*Main> searchr "hahal" "jupp" "hahahalala" "hahahalala"
The problem is that the string to replace may contain a repeated
Am Samstag, 10. Dezember 2005 02:51 schrieben Sie: pattern
and the pattern that begins the actual occurence might be consumed before a failure is detected.
Yes, I've corrected it. Now it is just 25% faster and that is only with -O2 flag. Here is whole thing, I hope there are no more bugs left :) :
None that sprang to my eyes. However, on my machine, yours is not faster than Lemmih's. Now, using the new Strings, I get the following times: -O2 -O1 no opt Lemmih's: 38.9 sec 38.9 sec 76.7 sec Yours : 40.1 sec 41.5 sec 131.1 sec Mine : 32.9 sec 33.1 sec 82.8 sec.
However, there's a problem with Lemmih's replace:
*Main> searchr "ababcab" "###" "ababcababcabab" "###abcab" *Main> replace "ababcab" "###" "ababcababcabab" "ababc###ab"
due to the fact that Lemmih's version scans the input from right to left (that's easily changed by a few reverses, though -- but costly for long inputs), more serious is
Prelude Main> replace "ja" "aja" "jjjjjjja" "ajajajajajajaja".
The fastest -- and nicely simple above -- that I could come up with is
replace :: String -> String -> String -> String replace _ _ "" = "" replace "" _ str = str replace src dst inp = process inp where n = length src process "" = "" process st@(c:cs) | src `isPrefixOf` st = dst ++ process (drop n st) | otherwise = c:process cs
It's roughly 10% faster than my other version on "seasearch" ... and if you try it on
main2 :: IO () main2 = let src = replicate 1000 'r' dst = " # " str = replicate 999 'r' ++ 'c': replicate 1000 'r' out = replace src dst $ concat $ replicate 500 str out1 = replace src dst $ concat $ replicate 501 str in do putStrLn $ "Working very long" putStrLn $ show (out == out1) ++ "\nDone"
you'll see a real difference. I'm not sure, why your algorithm pays a so much higher penalty, though. Maybe, it'll be faster if you make searchr' &c local functions? I'll try.
Cheers, Daniel
_________________________________________________________________ FREE pop-up blocking with the new MSN Toolbar - get it now! http://toolbar.msn.click-url.com/go/onm00200415ave/direct/01/
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe
_________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

From: "Branimir Maksimovic"
To: bmaxa@hotmail.com, daniel.is.fischer@web.de CC: Haskell-Cafe@haskell.org Subject: RE: [Haskell-cafe] RE: Substring replacements (was: Differences inoptimisiation Date: Sun, 11 Dec 2005 07:29:46 +0000 I've found one remaining bug, and this is corrected version.
Ah, I've forgot to include important optimisation, and patched around something else :) No wonder it was slow with normal test: ------------------------------------------------------------------------------- searchReplace :: String->String->String -> String searchReplace sr rp xs = searchr sr rp xs "" where searchr :: String->String->String->String -> String searchr [] _ xs _ = xs searchr _ _ [] _ = [] searchr sr rp xs rollBack | fst $ fst $ fnd rollBack = rp ++ searchr sr rp (snd $ snd $ fst $ fnd rollBack ) ( snd $ fnd rollBack) | otherwise = reverse ((fst $ snd $ fst $ fnd rollBack) ++ rollBack) ++ searchr sr rp (snd $ snd $ fst $ fnd rollBack) ( snd $ fnd rollBack) where fnd = searchr' sr xs "" searchr' :: String->String->String->String -> ((Bool,(String,String)),String) searchr' (sr:srs) xs fndSoFar rollBack = searchr'' (drop (length rollBack) (sr:srs)) xs fndSoFar (False,False,"") sr searchr'' :: String->String->String->(Bool,Bool,String)->Char -> ((Bool,(String,String)),String) searchr'' [] xs fnd _ _ = ((True,(fnd,xs)),"") searchr'' _ [] fnd (_,_,rollBack) _ = ((False,(fnd,[])),rollBack) searchr'' (sr:srs) (x:xs) fndSoFar (cnt,f,rollBack) s | sr == x = if cnt && (f || s == x) then searchr'' srs xs fndSoFar (True,True,x:rollBack) s else searchr'' srs xs (x:fndSoFar) (True,False,"") s | otherwise = if not f then if s == x then ((False,(fndSoFar,x:xs)),"") else ((False,searchr''' s xs (x:fndSoFar)),"") else ((False,(fndSoFar, x:xs)),rollBack) searchr''' :: Char->String->String -> (String,String) searchr''' sr [] fndSoFar = (fndSoFar,[]) searchr''' sr (x:xs) fndSoFar | sr/=x = searchr''' sr xs (x:fndSoFar) | otherwise = (fndSoFar,x:xs) ------------------------------------------------------------------------------- _________________________________________________________________ Don't just search. Find. Check out the new MSN Search! http://search.msn.com/

Unfortunately: Prelude SearchRep> searchReplace "aabaabba" "iii" "aabaabaabbaa" "aabaabaabb" Prelude SearchRep> searchReplace "abaaba" "-" "abaaabaaba" "abaaabaab" Seemingly, your algorithm assumes that the last component of the result of search'' is the beginning of the searched for pattern reversed -- which needn't be. One comment on style (I like it in general): IMHO, the use of nested pairs and combinations of fst, snd is not very readable, using triples/quadruples and providing your own accessor-functions (e.g. fst3, thd4) would improve that -- it might have an impact on performance, though, that would require a test or an answer from somebody more knowledgeable. And -- I'm not sure whether that is indeed so -- if you have an argument pattern (x:xs) which may be directly returned, as in fun (x:xs) | even x = ([x],xs) | otherwise = ([],x:xs) the list would have to be reconstructed from its head and tail, which could be avoided by using an as-pattern fun xxs@(x:xs) | even x = ([x],xs) | otherwise = ([],xxs), however, that wouldn't be significant unless it happens really often and the compiler might optimise it away anyway. And on my test, yesterday, Tomasz' version took 40s, my first 45s, Henning's 77s and yours 170s, Bulat's beat them all with 29s, your version from below took less than 1s, but if we took a search pattern like above, it wouldn't do the correct replacements. Cheers, Daniel Am Sonntag, 11. Dezember 2005 10:08 schrieben Sie:
From: "Branimir Maksimovic"
To: bmaxa@hotmail.com, daniel.is.fischer@web.de CC: Haskell-Cafe@haskell.org Subject: RE: [Haskell-cafe] RE: Substring replacements (was: Differences inoptimisiation Date: Sun, 11 Dec 2005 07:29:46 +0000
I've found one remaining bug, and this is corrected version.
Ah, I've forgot to include important optimisation, and patched around something else :) No wonder it was slow with normal test: --------------------------------------------------------------------------- ---- searchReplace :: String->String->String -> String searchReplace sr rp xs = searchr sr rp xs "" where searchr :: String->String->String->String -> String searchr [] _ xs _ = xs searchr _ _ [] _ = [] searchr sr rp xs rollBack
| fst $ fst $ fnd rollBack = rp
++ searchr sr rp (snd $ snd $ fst $ fnd rollBack ) ( snd $ fnd rollBack)
| otherwise = reverse ((fst $ snd $ fst $ fnd rollBack) ++
rollBack) ++ searchr sr rp (snd $ snd $ fst $ fnd rollBack) ( snd $ fnd rollBack) where fnd = searchr' sr xs ""
searchr' :: String->String->String->String -> ((Bool,(String,String)),String) searchr' (sr:srs) xs fndSoFar rollBack = searchr'' (drop (length rollBack) (sr:srs)) xs fndSoFar (False,False,"") sr
searchr'' :: String->String->String->(Bool,Bool,String)->Char -> ((Bool,(String,String)),String) searchr'' [] xs fnd _ _ = ((True,(fnd,xs)),"") searchr'' _ [] fnd (_,_,rollBack) _ = ((False,(fnd,[])),rollBack) searchr'' (sr:srs) (x:xs) fndSoFar (cnt,f,rollBack) s
| sr == x = if cnt && (f || s == x)
then searchr'' srs xs fndSoFar (True,True,x:rollBack) s else searchr'' srs xs (x:fndSoFar) (True,False,"") s
| otherwise = if not f
then if s == x then ((False,(fndSoFar,x:xs)),"") else ((False,searchr''' s xs (x:fndSoFar)),"") else ((False,(fndSoFar, x:xs)),rollBack)
searchr''' :: Char->String->String -> (String,String) searchr''' sr [] fndSoFar = (fndSoFar,[]) searchr''' sr (x:xs) fndSoFar | sr/=x = searchr''' sr xs (x:fndSoFar)
| otherwise = (fndSoFar,x:xs)
--------------------------------------------------------------------------- ----
_________________________________________________________________ Don't just search. Find. Check out the new MSN Search! http://search.msn.com/

From: Daniel Fischer
To: "Branimir Maksimovic" CC: Haskell-Cafe@haskell.org Subject: Re: Substring replacements (was: Differences inoptimisiation Date: Sun, 11 Dec 2005 18:12:12 +0100 Unfortunately: Prelude SearchRep> searchReplace "aabaabba" "iii" "aabaabaabbaa" "aabaabaabb"
I've solved this case
Prelude SearchRep> searchReplace "abaaba" "-" "abaaabaaba" "abaaabaab"
This one is cleaned up, but searching have to be adjusted for false positive patterns. So I need some more time, as this isn't quick fix.
Seemingly, your algorithm assumes that the last component of the result of search'' is the beginning of the searched for pattern reversed -- which needn't be.
Yes. That is the problem. Now I have to compare if it fits with searched string.
One comment on style (I like it in general): IMHO, the use of nested pairs and combinations of fst, snd is not very readable, using triples/quadruples and providing your own accessor-functions (e.g. fst3, thd4) would improve that -- it might have an impact on performance, though, that would require a test or an answer from somebody more knowledgeable. And -- I'm not sure whether that is indeed so -- if you have an argument pattern (x:xs) which may be directly returned, as in
fun (x:xs) | even x = ([x],xs) | otherwise = ([],x:xs)
the list would have to be reconstructed from its head and tail, which could be avoided by using an as-pattern
fun xxs@(x:xs) | even x = ([x],xs) | otherwise = ([],xxs), however, that wouldn't be significant unless it happens really often and the compiler might optimise it away anyway.
Thank you! This really helps . I 'll clean up my mess a bit. Greetings, Bane. _________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

Hello Branimir, Sunday, December 11, 2005, 5:19:22 AM, you wrote: BM> After seeing your test, I've implemented full KMP algorithm, which BM> is blazingly fast with your test. It is slower in mine test due excessive are you seen http://haskell.org/hawiki/RunTimeCompilation ? can you formulate conditions when straightforward algorithm will be better and when KMP algorithm is preferred? it will be great to include both algorithms in standard libraries with guides when each one must be used -- Best regards, Bulat mailto:bulatz@HotPOP.com

From: Bulat Ziganshin
Reply-To: Bulat Ziganshin To: "Branimir Maksimovic" CC: daniel.is.fischer@web.de, Haskell-Cafe@haskell.org Subject: Re: [Haskell-cafe] RE: Substring replacements (was: Differences in optimisiation ...) Date: Sun, 11 Dec 2005 14:03:45 +0300 Hello Branimir,
Sunday, December 11, 2005, 5:19:22 AM, you wrote:
BM> After seeing your test, I've implemented full KMP algorithm, which BM> is blazingly fast with your test. It is slower in mine test due excessive
are you seen http://haskell.org/hawiki/RunTimeCompilation ?
Yes, that's the next step I will take.
can you formulate conditions when straightforward algorithm will be better and when KMP algorithm is preferred?
Startighforward is better when search string is relatively short and there are lot of matches or partial matches within searched string. Exellent example when one is faster then the other is my test when your algorithm is faster and Danilel's test where KMP excels. Greetings, Bane. _________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

Am Donnerstag, 8. Dezember 2005 19:17 schrieb Branimir Maksimovic:
From: Henning Thielemann
To: Branimir Maksimovic
CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive and compiled mode Date: Thu, 8 Dec 2005 18:38:45 +0100 (MET) On Thu, 8 Dec 2005, Branimir Maksimovic wrote:
program performs search replace on a String
http://www.haskell.org/pipermail/haskell-cafe/2005-April/009692.html
This is nice and ellegant but example search replace program runs more then 50% faster with my implementation.
Greetings, Bane.
That's probably because Lemmih's is polymorphic. Yesterday evening, I cooked up my own version srchrep :: String -> String -> String -> String srchrep "" rp st = st -- or should it rather be cycle rp ? srchrep sr rp st | sr == rp = st srchrep sr@(c:cs) rep inp = process inp where process str = case start "" str of Nothing -> str Just (pre, post) -> reverse pre ++ rep ++ process post start _ "" = Nothing start pre (s:st) | s == c = cont pre [s] cs st | otherwise = start (s:pre) st cont pre _ "" st = Just (pre, st) cont _ _ _ "" = Nothing cont pre fnd (p:pat) (s:st) | s == p && s == c = abort pre (p:fnd) pat st `mplus` cont (fnd ++ pre) [s] cs st | s == p = cont pre (p:fnd) pat st | s == c = cont (fnd ++ pre) [s] cs st | otherwise = start (s:fnd ++ pre) st abort pre _ "" st = Just (pre, st) abort pre fnd (p:pat) (s:st) | s == p = abort pre (s:fnd) pat st abort _ _ _ _ = Nothing and today I compared the versions, with Lemmih's type specialized to String -> ... -> String. Then Lemmih's is a bit faster than mine (a bit slower, if compiled for profiling) which is still a bit faster than yours (and, profiling, yours is significantly slower than the others. Cheers, Daniel

On 12/10/05, Daniel Fischer
Am Donnerstag, 8. Dezember 2005 19:17 schrieb Branimir Maksimovic:
From: Henning Thielemann
To: Branimir Maksimovic
CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive and compiled mode Date: Thu, 8 Dec 2005 18:38:45 +0100 (MET) On Thu, 8 Dec 2005, Branimir Maksimovic wrote:
program performs search replace on a String
http://www.haskell.org/pipermail/haskell-cafe/2005-April/009692.html
This is nice and ellegant but example search replace program runs more then 50% faster with my implementation.
Greetings, Bane.
That's probably because Lemmih's is polymorphic.
Didn't Henning Thielemann write it? -- Friendly, Lemmih

Am Samstag, 10. Dezember 2005 15:34 schrieben Sie:
On 12/10/05, Daniel Fischer
wrote: <snip> That's probably because Lemmih's is polymorphic.
Didn't Henning Thielemann write it?
-- Friendly, Lemmih I thought, Henning Thielemann == Lemmih. If I'm wrong, I apologize.
Cheers, Daniel

On 10/12/05, Daniel Fischer
Am Samstag, 10. Dezember 2005 15:34 schrieben Sie:
On 12/10/05, Daniel Fischer
wrote: <snip> That's probably because Lemmih's is polymorphic.
Didn't Henning Thielemann write it?
-- Friendly, Lemmih I thought, Henning Thielemann == Lemmih. If I'm wrong, I apologize.
Cheers, Daniel
Lemmih is David Himmelstrup http://haskell.org/hawiki/DavidHimmelstrup :)

Am Samstag, 10. Dezember 2005 23:22 schrieben Sie:
On 10/12/05, Daniel Fischer
wrote: Am Samstag, 10. Dezember 2005 15:34 schrieben Sie:
On 12/10/05, Daniel Fischer
wrote: <snip>
That's probably because Lemmih's is polymorphic.
Didn't Henning Thielemann write it?
-- Friendly, Lemmih
I thought, Henning Thielemann == Lemmih. If I'm wrong, I apologize.
Cheers, Daniel
Lemmih is David Himmelstrup http://haskell.org/hawiki/DavidHimmelstrup :)
Stupid me, I confused lemming and Lemmih. I hope nobody feels insulted. Daniel

On Sat, 10 Dec 2005, Daniel Fischer wrote:
Am Samstag, 10. Dezember 2005 15:34 schrieben Sie:
On 12/10/05, Daniel Fischer
wrote: <snip> That's probably because Lemmih's is polymorphic.
Didn't Henning Thielemann write it?
-- Friendly, Lemmih I thought, Henning Thielemann == Lemmih. If I'm wrong, I apologize.
You are wrong. :-) -- 'Lemmih' is not polymorphic! :-]

From: Daniel Fischer
To: "Branimir Maksimovic" CC: Haskell-Cafe@haskell.org Subject: Re: Differences in optimisiation with interactive and compiled mo Date: Sat, 10 Dec 2005 15:11:31 +0100 Am Donnerstag, 8. Dezember 2005 19:17 schrieb Branimir Maksimovic:
From: Henning Thielemann
To: Branimir Maksimovic
CC: haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive and compiled mode Date: Thu, 8 Dec 2005 18:38:45 +0100 (MET) On Thu, 8 Dec 2005, Branimir Maksimovic wrote:
program performs search replace on a String
http://www.haskell.org/pipermail/haskell-cafe/2005-April/009692.html
This is nice and ellegant but example search replace program runs more then 50% faster with my implementation.
Greetings, Bane.
That's probably because Lemmih's is polymorphic. Yesterday evening, I cooked up my own version
Then Lemmih's is a bit faster than mine (a bit slower, if compiled for profiling) which is still a bit faster than yours (and, profiling, yours is significantly slower than the others.
I've fixed function signatures for strings only. this is my test: $ ghc -fglasgow-exts -O2 srchrep.hs --make -o srchrep.exe Chasing modules from: srchrep.hs Compiling Main ( srchrep.hs, srchrep.o ) Linking ... bmaxa@MAXA ~/tutorial $ ghc -fglasgow-exts -O2 replace.hs --make -o replace.exe Chasing modules from: replace.hs Compiling Main ( replace.hs, replace.o ) Linking ... bmaxa@MAXA ~/tutorial $ ghc -fglasgow-exts -O2 searchr.hs --make -o searchr.exe Chasing modules from: searchr.hs Compiling Main ( searchr.hs, searchr.o ) Linking ... bmaxa@MAXA ~/tutorial $ time ./searchr. searchr.exe searchr.hi searchr.hs searchr.o bmaxa@MAXA ~/tutorial $ time ./searchr.exe Working:seaseasearch replace able seaseaseasearch baker seaseasearch charlie True Done real 0m12.547s user 0m0.015s sys 0m0.000s bmaxa@MAXA ~/tutorial $ time ./replace.exe Working:seaseasearch replace able seaseaseasearch baker seaseasearch charlie True Done real 0m21.078s user 0m0.015s sys 0m0.015s bmaxa@MAXA ~/tutorial $ time ./srchrep.exe Working:seaseasearch replace able seaseaseasearch baker seaseasearch charlie True Done real 0m12.188s user 0m0.015s sys 0m0.000s Your version seems fastest. Greetings, Bane. _________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

On Thu, Dec 08, 2005 at 06:38:45PM +0100, Henning Thielemann wrote:
On Thu, 8 Dec 2005, Branimir Maksimovic wrote:
program performs search replace on a String
http://www.haskell.org/pipermail/haskell-cafe/2005-April/009692.html
Neat! However, it breaks the following nice (but perhaps not useful?) property: replace x y z == reverse (replace (reverse x) (reverse y) (reverse z)) Example: *SearchRepl> replace "ab" "ba" "aaaaaaaaab" "baaaaaaaaa" *SearchRepl> reverse (replace (reverse "ab") (reverse "ba") (reverse "aaaaaaaaab")) "aaaaaaaaba" Is this a feature or bug? Best regards Tomasz -- I am searching for a programmer who is good at least in some of [Haskell, ML, C++, Linux, FreeBSD, math] for work in Warsaw, Poland

On Sat, Dec 10, 2005 at 03:24:56PM +0100, Tomasz Zielonka wrote:
*SearchRepl> replace "ab" "ba" "aaaaaaaaab" "baaaaaaaaa"
It also shows that your implementation is not lazy, so it couldn't be used for infinite lists. In some situations, even for short patterns, it just has to check the whole input list to produce the first element of output list. Anyway, I still like the code :-) Best regards Tomasz -- I am searching for a programmer who is good at least in some of [Haskell, ML, C++, Linux, FreeBSD, math] for work in Warsaw, Poland

On Sat, Dec 10, 2005 at 03:29:49PM +0100, Tomasz Zielonka wrote:
On Sat, Dec 10, 2005 at 03:24:56PM +0100, Tomasz Zielonka wrote:
*SearchRepl> replace "ab" "ba" "aaaaaaaaab" "baaaaaaaaa"
It also shows that your implementation is not lazy, so it couldn't be used for infinite lists. In some situations, even for short patterns, it just has to check the whole input list to produce the first element of output list.
Here is my implementation replace src dst = repl where repl input = dst ++ repl (drop (length src) input) repl (x:xs) = x : repl xs repl [] = [] which should be infinite list friendly. Best regards Tomasz -- I am searching for a programmer who is good at least in some of [Haskell, ML, C++, Linux, FreeBSD, math] for work in Warsaw, Poland

From: Tomasz Zielonka
To: Henning Thielemann CC: Branimir Maksimovic , haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive and compiled mode Date: Sat, 10 Dec 2005 15:36:57 +0100 On Sat, Dec 10, 2005 at 03:29:49PM +0100, Tomasz Zielonka wrote:
On Sat, Dec 10, 2005 at 03:24:56PM +0100, Tomasz Zielonka wrote:
*SearchRepl> replace "ab" "ba" "aaaaaaaaab" "baaaaaaaaa"
It also shows that your implementation is not lazy, so it couldn't be used for infinite lists. In some situations, even for short patterns, it just has to check the whole input list to produce the first element of output list.
Here is my implementation
replace src dst = repl where repl input = dst ++ repl (drop (length src) input) repl (x:xs) = x : repl xs repl [] = []
which should be infinite list friendly.
Nice code. But it takes lot of ram (1GB is not enough )and can't execute my test. Other versions don't take that much ram. Actually just 2mb each but yours somehow didn't work well with optimiser. I don't know why. Greetings, Bane. _________________________________________________________________ Don't just search. Find. Check out the new MSN Search! http://search.msn.click-url.com/go/onm00200636ave/direct/01/

On Sat, Dec 10, 2005 at 04:14:20PM +0000, Branimir Maksimovic wrote:
Nice code.
But incorrect. I have broken it when refactoring :-/ Here is the correct version: replace2 src dst = repl where repl input | src `isPrefixOf` input = dst ++ repl (drop (length src) input) repl (x:xs) = x : repl xs repl [] = []
But it takes lot of ram (1GB is not enough )and can't execute my test.
Can you check this version? Best regards Tomasz -- I am searching for a programmer who is good at least in some of [Haskell, ML, C++, Linux, FreeBSD, math] for work in Warsaw, Poland

From: Tomasz Zielonka
To: Branimir Maksimovic CC: lemming@henning-thielemann.de, haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive and compiled mo Date: Sat, 10 Dec 2005 18:14:58 +0100 On Sat, Dec 10, 2005 at 04:14:20PM +0000, Branimir Maksimovic wrote:
Nice code.
But incorrect. I have broken it when refactoring :-/
Here is the correct version:
replace2 src dst = repl where repl input | src `isPrefixOf` input = dst ++ repl (drop (length src) input) repl (x:xs) = x : repl xs repl [] = []
But it takes lot of ram (1GB is not enough )and can't execute my test.
Can you check this version? It's ok now; 2 megs like other versions. It's just about 1.5 seconds slower then mine version and Daniels version is a bit faster the mine.
bmaxa@MAXA ~/tutorial $ time ./replace1.exe Working:seaseasearch replace able seaseaseasearch baker seaseasearch charlie True Done real 0m14.140s user 0m0.015s sys 0m0.000s Greetings, Bane. _________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

Have you tried using any of the standard string searching algorithms to speed up the search? Like BM or KMP? -- Lennart Branimir Maksimovic wrote:
From: Tomasz Zielonka
To: Branimir Maksimovic CC: lemming@henning-thielemann.de, haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive and compiled mo Date: Sat, 10 Dec 2005 18:14:58 +0100 On Sat, Dec 10, 2005 at 04:14:20PM +0000, Branimir Maksimovic wrote:
Nice code.
But incorrect. I have broken it when refactoring :-/
Here is the correct version:
replace2 src dst = repl where repl input | src `isPrefixOf` input = dst ++ repl (drop (length src) input) repl (x:xs) = x : repl xs repl [] = []
But it takes lot of ram (1GB is not enough )and can't execute my test.
Can you check this version?
It's ok now; 2 megs like other versions. It's just about 1.5 seconds slower then mine version and Daniels version is a bit faster the mine.
bmaxa@MAXA ~/tutorial $ time ./replace1.exe Working:seaseasearch replace able seaseaseasearch baker seaseasearch charlie True Done
real 0m14.140s user 0m0.015s sys 0m0.000s
Greetings, Bane.
_________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Hello Branimir, Saturday, December 10, 2005, 8:29:09 PM, you wrote:
Can you check this version?
and this: replace from to = repl where repl s | Just remainder <- start_from from s = to ++ repl remainder repl (c:cs) = c : repl cs repl [] = [] start_from (x:xs) (y:ys) | x==y = start_from xs ys start_from [] str = Just str start_from _ _ = Nothing -- Best regards, Bulat mailto:bulatz@HotPOP.com

From: Bulat Ziganshin
Reply-To: Bulat Ziganshin To: "Branimir Maksimovic" CC: tomasz.zielonka@gmail.com, lemming@henning-thielemann.de,haskell-cafe@haskell.org Subject: Re[2]: [Haskell-cafe] Differences in optimisiation with interactive and compiled mo Date: Sun, 11 Dec 2005 00:42:24 +0300 Hello Branimir,
Saturday, December 10, 2005, 8:29:09 PM, you wrote:
Can you check this version?
and this:
replace from to = repl where repl s | Just remainder <- start_from from s = to ++ repl remainder repl (c:cs) = c : repl cs repl [] = []
start_from (x:xs) (y:ys) | x==y = start_from xs ys start_from [] str = Just str start_from _ _ = Nothing
This one is fastest,not much, but is. So here it goes: your version, then Daniel's, then mine. Greetings, Bane. _________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

On Sun, 11 Dec 2005, Branimir Maksimovic wrote:
This one is fastest,not much, but is. So here it goes: your version, then Daniel's, then mine.
What about a Wiki page containing a search&replace function competition? :-]

Am Samstag, 10. Dezember 2005 22:42 schrieb Bulat Ziganshin:
Hello Branimir,
Saturday, December 10, 2005, 8:29:09 PM, you wrote:
Can you check this version?
and this:
replace from to = repl where repl s | Just remainder <- start_from from s = to ++ repl remainder repl (c:cs) = c : repl cs repl [] = []
start_from (x:xs) (y:ys) | x==y = start_from xs ys start_from [] str = Just str start_from _ _ = Nothing
This is the fastest, even without type signatures (those give a wee bit of extra speed). Have you any idea why using a pattern guard is faster (not much, but consistently) than the equivalent case-expression? Cheers, Daniel

From: Daniel Fischer
To: Bulat Ziganshin CC: Haskell-Cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive andcompiled mo Date: Sun, 11 Dec 2005 14:59:55 +0100 Am Samstag, 10. Dezember 2005 22:42 schrieb Bulat Ziganshin:
Hello Branimir,
Saturday, December 10, 2005, 8:29:09 PM, you wrote:
Can you check this version?
and this:
replace from to = repl where repl s | Just remainder <- start_from from s = to ++ repl remainder repl (c:cs) = c : repl cs repl [] = []
start_from (x:xs) (y:ys) | x==y = start_from xs ys start_from [] str = Just str start_from _ _ = Nothing
This is the fastest, even without type signatures (those give a wee bit of extra speed).
your test (unlikely in real scenario): $ time replace1 Working very long False Done real 0m12.531s user 0m0.015s sys 0m0.000s my test is not any more 0.25 secs with your test, becasue I've sacrifised that for my test speed :) bmaxa@MAXA ~/tutorial $ time searchr Working very long True Done real 0m4.000s user 0m0.031s sys 0m0.000s my test: bmaxa@MAXA ~/tutorial $ ghc -fglasgow-exts -O2 replace1.hs --make -o replace1.exe Chasing modules from: replace1.hs Compiling Main ( replace1.hs, replace1.o ) Linking ... bmaxa@MAXA ~/tutorial $ ghc -fglasgow-exts -O2 searchr.hs --make -o searchr.exe Chasing modules from: searchr.hs Compiling Main ( searchr.hs, searchr.o ) Linking ... bmaxa@MAXA ~/tutorial $ time replace1 Working:seasearch replace able seaseasearch baker seasearch charlie True Done real 0m11.718s user 0m0.015s sys 0m0.015s bmaxa@MAXA ~/tutorial $ time searchr.exe Working:seasearch replace able seaseasearch baker seasearch charlie True Done real 0m13.921s user 0m0.015s sys 0m0.015s
Have you any idea why using a pattern guard is faster (not much, but consistently) than the equivalent case-expression?
Probably because either then function is better inlined, or there is optimised tail recursion. In any way ghc very well optimises recursion. I didn't notice any difference in speed whether function signature is tagged only for strings or is polymorphic. So we can freely make polymorphic signatures. Greetings, Bane. _________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

Am Samstag, 10. Dezember 2005 18:29 schrieb Branimir Maksimovic:
From: Tomasz Zielonka
To: Branimir Maksimovic
CC: lemming@henning-thielemann.de, haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive and compiled mo Date: Sat, 10 Dec 2005 18:14:58 +0100 On Sat, Dec 10, 2005 at 04:14:20PM +0000, Branimir Maksimovic wrote:
Nice code.
But incorrect. I have broken it when refactoring :-/
Here is the correct version:
replace2 src dst = repl where repl input | src `isPrefixOf` input = dst ++ repl (drop (length src) input) repl (x:xs) = x : repl xs repl [] = []
But it takes lot of ram (1GB is not enough )and can't execute my test.
Can you check this version?
It's ok now; 2 megs like other versions. It's just about 1.5 seconds slower then mine version and Daniels version is a bit faster the mine.
bmaxa@MAXA ~/tutorial $ time ./replace1.exe Working:seaseasearch replace able seaseaseasearch baker seaseasearch charlie True Done
real 0m14.140s user 0m0.015s sys 0m0.000s
Greetings, Bane.
On my thingy, Tomasz' version is a bit faster than my version of the same algorithm for seasea..., and a bit slower for rrrrrrrrrrrrrrrr... and this algorithm is definitely the fastest submitted. Odd that your timings are different (in order) -- maybe it's something about Linux vs. Windows? Cheers, Daniel

From: Daniel Fischer
To: "Branimir Maksimovic" CC: Haskell-Cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive and compiled mo Date: Sat, 10 Dec 2005 23:56:28 +0100 Am Samstag, 10. Dezember 2005 18:29 schrieb Branimir Maksimovic:
From: Tomasz Zielonka
To: Branimir Maksimovic
CC: lemming@henning-thielemann.de, haskell-cafe@haskell.org Subject: Re: [Haskell-cafe] Differences in optimisiation with interactive and compiled mo Date: Sat, 10 Dec 2005 18:14:58 +0100 On Sat, Dec 10, 2005 at 04:14:20PM +0000, Branimir Maksimovic wrote:
Nice code.
But incorrect. I have broken it when refactoring :-/
Here is the correct version:
replace2 src dst = repl where repl input | src `isPrefixOf` input = dst ++ repl (drop (length src) input) repl (x:xs) = x : repl xs repl [] = []
But it takes lot of ram (1GB is not enough )and can't execute my test.
Can you check this version?
It's ok now; 2 megs like other versions. It's just about 1.5 seconds slower then mine version and Daniels version is a bit faster the mine.
bmaxa@MAXA ~/tutorial $ time ./replace1.exe Working:seaseasearch replace able seaseaseasearch baker seaseasearch charlie True Done
real 0m14.140s user 0m0.015s sys 0m0.000s
Greetings, Bane.
On my thingy, Tomasz' version is a bit faster than my version of the same algorithm for seasea..., and a bit slower for rrrrrrrrrrrrrrrr... and this algorithm is definitely the fastest submitted. Odd that your timings are different (in order) -- maybe it's something about Linux vs. Windows?
Well, I have same results on linux , though I just compared two versions. I think that it because I uise -O2 flag. mine version does benefit with it (perhaps less temporaries and more inlines? ) What's the difference between -O2 and -O because I see noticable difference with my version? Greetings, Bane. _________________________________________________________________ Express yourself instantly with MSN Messenger! Download today it's FREE! http://messenger.msn.click-url.com/go/onm00200471ave/direct/01/

On Sat, 10 Dec 2005, Tomasz Zielonka wrote:
On Thu, Dec 08, 2005 at 06:38:45PM +0100, Henning Thielemann wrote:
On Thu, 8 Dec 2005, Branimir Maksimovic wrote:
program performs search replace on a String
http://www.haskell.org/pipermail/haskell-cafe/2005-April/009692.html
Neat!
However, it breaks the following nice (but perhaps not useful?) property:
replace x y z == reverse (replace (reverse x) (reverse y) (reverse z))
It replaces things that are already replaced. So it is not quite correct.
participants (8)
-
Branimir Maksimovic
-
Bulat Ziganshin
-
Cale Gibbard
-
Daniel Fischer
-
Henning Thielemann
-
Lemmih
-
Lennart Augustsson
-
Tomasz Zielonka