[Haskell-cafe] "computational time" always 0.0 in this example...
Lennart
lray at l-ray.de
Thu Dec 7 08:59:57 EST 2006
Hi,
with the following code, I want to measure the time being needed to
execute the algorithm. But the result is always 0.0.
import Char (toLower)
import Maybe
import List ( delete, sort, intersect )
import System.CPUTime
import Control.Exception
import Debug.Trace
fromInt = fromIntegral
wordList2 :: [String]
wordList2 = ["Sam J Chapman",
"Samuel Chapman",
"S Chapman",
"Samuel John Chapman",
"John Smith",
"Richard Smith",
"aaaa mnop zzzz",
"bbbb mnop yyyy",
"aa mnop zzzzzz",
"a ",
"aaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaaa",
"aaaa bcdefgh mmmmmmmm stuvwx zzzzzz",
"jjjj bcdefgh qqqqqqqq stuvx yyyyyy",
"aaaaa bcdefgh stuvwx zzzzzz",
"aaaaa aaaaa aaaaa zzzzzz",
"aaaaa aaaaa"]
time :: IO t -> IO t
time a = do
start <- getCPUTime
v <- a
end <- getCPUTime
let diff = (fromIntegral (end - start)) / (10^12)
-- let diff = (fromIntegral (end - start))
putStrLn "Computation time:"
print (diff :: Double)
return v
main = do
putStrLn "Starting..."
time $ doTest wordList2 wordList2 `seq` return ()
putStrLn "Done."
test3 = let loop = getCPUTime >>= print >> loop in loop
doTest :: [String] -> [String] -> [ Double ]
doTest [] _ = []
doTest (x:xs) [] = doTest xs xs
doTest (x:xs) (y:ys) = result : (doTest (x:xs) (ys))
where result = qGramMetrics2 x y
qGramMetrics2:: String -> String -> Double
qGramMetrics2 t1 t2 = let i = intersect (qGramList (map toLower t1) 3)
(qGramList (map toLower t2) 3)
il = fromInt (length i)
ml = fromInt ((max (length t1) (length t2)) - 1 )
in (il / ml )
-- list of chars within list of qgrams
qGramList :: String -> Int -> [[Char]]
qGramList [] _ = []
qGramList (x:[]) _ = []
qGramList (x:xs) i1 = (x: take (i1 - 1) xs):(qGramList xs i1)
-- list of chars within list of qgrams
numberedQgramListWithStart :: String -> Int -> [(Int, [Char])]
numberedQgramListWithStart x i1 = let prefix = replicate (i1-1) '#'
suffix = replicate (i1-1) '$'
in numberedQgramList (prefix++(x++suffix)) i1 0
numberedQgramList :: String -> Int -> Int -> [(Int, [Char])]
numberedQgramList [] _ _ = []
numberedQgramList (x:xs) i1 i2
-- add the dollar-sign
| (length xs) < i1 && x=='$'= []
| otherwise = (i2,(x: take (i1 - 1) xs)):(numberedQgramList
xs i1 (i2+1))
Am using ghci 6.6 under a Kubuntu 6.10 Linux.
time $ product [1..1000] `seq` return ()
instead of
time $ doTest wordList2 wordList2 `seq` return ()
works fine.
things like
time $ print (doTest wordList2 wordList2) `seq` return () or
time $ length (doTest wordList2 wordList2) `seq` return () or
time $ trace (doTest wordList2 wordList2) `seq` return ()
didn't work.
Am desperated...
Lennart
More information about the Haskell-Cafe
mailing list