Re: Re: [Haskell-cafe] computational time always 0.0 in this example...

2006-12-08 Thread Lennart

The time $ evaluate (sum (doTest wordList2 wordList2))
works fine for me... ...and the :set +s is gorgeous as well!

Thanks for the help!

Lennart


Lemmih wrote:

On 12/7/06, Lennart [EMAIL PROTECTED] wrote:

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,
    mnop ,
    mnop ,
   aa mnop zz,
   a ,
   aa,
    bcdefgh  stuvwx zz,
    bcdefgh  stuvx yy,
   a bcdefgh stuvwx zz,
   a a a zz,
   a a]

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...


Try:

time $ evaluate (sum (doTest wordList2 wordList2))




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] computational time always 0.0 in this example...

2006-12-07 Thread Lennart

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,
   mnop ,
   mnop ,
  aa mnop zz,
  a ,
  aa,
   bcdefgh  stuvwx zz,
   bcdefgh  stuvx yy,
  a bcdefgh stuvwx zz,
  a a a zz,
  a a]

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

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] computational time always 0.0 in this example...

2006-12-07 Thread Philippa Cowderoy
On Thu, 7 Dec 2006, Lennart wrote:

 Hi,
 
 with the following code, I want to measure the time being needed to execute
 the algorithm. But the result is always 0.0.
 

You need to do something to force the result of a, or it'll never actually 
get evaluated. Depending on the type in question, seq may or may not be 
enough. Printing it'll make you pay the cost of show, too.

-- 
[EMAIL PROTECTED]

There is no magic bullet. There are, however, plenty of bullets that
magically home in on feet when not used in exactly the right circumstances.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] computational time always 0.0 in this example...

2006-12-07 Thread Lemmih

On 12/7/06, Lennart [EMAIL PROTECTED] wrote:

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,
    mnop ,
    mnop ,
   aa mnop zz,
   a ,
   aa,
    bcdefgh  stuvwx zz,
    bcdefgh  stuvx yy,
   a bcdefgh stuvwx zz,
   a a a zz,
   a a]

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...


Running 'doTest wordList2 wordList2' takes less than 0.00s. Find a
more time consuming function and you will be fine.
Also, have a look at ':set +s' in ghci
(http://www.haskell.org/ghc/docs/latest/html/users_guide/ghci-set.html).

--
Cheers,
 Lemmih
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] computational time always 0.0 in this example...

2006-12-07 Thread Bulat Ziganshin
Hello Lennart,

Thursday, December 7, 2006, 4:59:57 PM, you wrote:

 time $ product [1..1000] `seq` return ()
 instead of
 time $ doTest wordList2 wordList2 `seq` return ()
 works fine.

because 'product' returns just one value. use the following:

time $ (return $! last (doTest wordList2 wordList2))


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] computational time always 0.0 in this example...

2006-12-07 Thread Lemmih

On 12/7/06, Lennart [EMAIL PROTECTED] wrote:

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,
    mnop ,
    mnop ,
   aa mnop zz,
   a ,
   aa,
    bcdefgh  stuvwx zz,
    bcdefgh  stuvx yy,
   a bcdefgh stuvwx zz,
   a a a zz,
   a a]

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...


Try:

time $ evaluate (sum (doTest wordList2 wordList2))


--
Cheers,
 Lemmih
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe