[Haskell-cafe] Re: Differences in optimisiation with interactive and compiled mo

Branimir Maksimovic bmaxa at hotmail.com
Fri Dec 9 20:51:40 EST 2005




>From: Daniel Fischer <daniel.is.fischer at web.de>
>To: "Branimir Maksimovic" <bmaxa at hotmail.com>
>CC: Haskell-Cafe at 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
>
>Am Freitag, 9. Dezember 2005 10:24 schrieb Branimir Maksimovic:
> > From: Henning Thielemann <lemming at henning-thielemann.de>
> >
> > >To: Branimir Maksimovic <bmaxa at hotmail.com>
> > >CC: haskell-cafe at 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 <lemming at henning-thielemann.de>
> > >>>To: Branimir Maksimovic <bmaxa at hotmail.com>
> > >>>CC: haskell-cafe at 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.
> >
>

_________________________________________________________________
Don't just search. Find. Check out the new MSN Search! 
http://search.msn.click-url.com/go/onm00200636ave/direct/01/



More information about the Haskell-Cafe mailing list