[Haskell-cafe] Differences in optimisiation with interactive and compiled mode

Cale Gibbard cgibbard at gmail.com
Thu Dec 8 09:26:11 EST 2005


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 <bmaxa at hotmail.com> 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 at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>


More information about the Haskell-Cafe mailing list