Hi,

        I am getting really strange results using the Time module of ghc
4.04 (patchlevel 1) under Solaris/SPARC and Linux/x86.

        My application is quite simple. It just retrives the system time
in two diferent moments during the execution of my code using
"Time.getClockTime" function. After that, I compute the elapsed time using
the "Time.diffClockTimes". The strange behavior can be seen when I try to
print the result using a show function over the "TimeDiff": Sometimes I
get negative seconds and/or negative picoseconds that does not make any
sense to me. But this is not happening all the time: Sometimes, I get the
correct number of seconds and pico seconds.

        Here we have some examples:

------------------------------------------------------------------
Start: Tue Oct 19 14:41:57 EDT 1999
End:   Tue Oct 19 14:41:58 EDT 1999
Elapsed Time: 0 hours, 0 min, 1 sec, 3863000000 picosec

Start: Tue Oct 19 14:41:58 EDT 1999
End:   Tue Oct 19 14:41:59 EDT 1999
Elapsed Time: 0 hours, 0 min, 1 sec, -16093000000 picosec

Start: Tue Oct 19 14:41:59 EDT 1999
End:   Tue Oct 19 14:42:00 EDT 1999
Elapsed Time: 0 hours, 1 min, -59 sec, -5933000000 picosec

Start: Tue Oct 19 14:42:00 EDT 1999
End:   Tue Oct 19 14:42:01 EDT 1999
Elapsed Time: 0 hours, 0 min, 1 sec, -305000000 picosec

Start: Tue Oct 19 14:42:02 EDT 1999
End:   Tue Oct 19 14:42:02 EDT 1999
Elapsed Time: 0 hours, 0 min, 0 sec, 954406000000 picosec

Start: Tue Oct 19 14:42:03 EDT 1999
End:   Tue Oct 19 14:42:04 EDT 1999
Elapsed Time: 0 hours, 0 min, 1 sec, 152582000000 picosec
-------------------------------------------------------------------

        My piece of code can be seen below:

------------------------------------------------------------------
module Main (main) where 

import Time
import CPUTime

infixl 9 >.>
(>.>) :: (t -> u) -> (u -> v) -> (t -> v)
f >.> g = g . f

apply :: (t -> u) -> t -> IO u
apply f a = return (f a)

main :: IO ()
main = (recall_time []) >>=          -- Recall time before the computation
       (show_time "Start: ") >>= 
       (lost_time 1000) >>=          -- Loop about 5 sec
       recall_time >>=               -- Recall time after the computation
       (show_time "End:   ") >>=
           (elapsed_time >.> to_string >.>
           ("Elapsed Time: " ++) >.> (++ "\n") >.> putStr)

-- This function loops during n miliseconds at least
lost_time :: Integer -> ([ClockTime] -> IO [ClockTime]) 
lost_time n = \t -> while (getCPUTime >>= apply (<= (n*1000000000)))
                          (return ())
                    >> return t
 
-- "while" definition
while test oper = 
        loop
        where loop = test >>= \result ->
                if result then (oper >> loop)
                          else return ()

-- Return a function that receives a time list and append to it,
-- as the first element, the current time
recall_time :: ([ClockTime] -> IO [ClockTime])
recall_time = 
                \l -> getClockTime >>= apply (:l)

-- Return a function that receives a time list and print the first
-- element
show_time :: String -> ([ClockTime] -> IO [ClockTime])
show_time str =
        \r@(a:x) -> putStr (str ++ (show a) ++ "\n")
                >> return r

-- Return the elapsed time
elapsed_time :: [ClockTime] -> TimeDiff
elapsed_time x = diffClockTimes (head x) (last x)


-- Return the TimeDiff as a string
to_string :: TimeDiff -> String
to_string (TimeDiff year month day hour min sec picosec) =
        show hour ++ " hours, " ++ show min ++ " min, " ++ show sec ++
        " sec, " ++ show picsec ++ " picosec"

-----------------------------------------------------------------------

        Can anyone tell me what is wrong with the libraries or exists any
trick to use the Time module?!

        Thanks for any help.

-----------------------------------------------------------
    Hermann Oliveira Rodrigues - [EMAIL PROTECTED]
        Computer Science Student at UFMG - Brazil
-----------------------------------------------------------
 A friend is one who knows all about you and likes you
 anyway.
        Christi Mary Warner



Reply via email to