add GHC.HetMet.{hetmet_kappa,hetmet_kappa_app}
[ghc-base.git] / System / CPUTime.hsc
1 {-# LANGUAGE CPP, NondecreasingIndentation, ForeignFunctionInterface #-}
2
3 -----------------------------------------------------------------------------
4 -- |
5 -- Module      :  System.CPUTime
6 -- Copyright   :  (c) The University of Glasgow 2001
7 -- License     :  BSD-style (see the file libraries/base/LICENSE)
8 -- 
9 -- Maintainer  :  libraries@haskell.org
10 -- Stability   :  provisional
11 -- Portability :  portable
12 --
13 -- The standard CPUTime library.
14 --
15 -----------------------------------------------------------------------------
16
17 module System.CPUTime 
18         (
19          getCPUTime,       -- :: IO Integer
20          cpuTimePrecision  -- :: Integer
21         ) where
22
23 import Prelude
24
25 import Data.Ratio
26
27 #ifdef __HUGS__
28 import Hugs.Time ( getCPUTime, clockTicks )
29 #endif
30
31 #ifdef __NHC__
32 import CPUTime ( getCPUTime, cpuTimePrecision )
33 #endif
34
35 #ifdef __GLASGOW_HASKELL__
36 import Foreign hiding (unsafePerformIO)
37 import Foreign.C
38 #if !defined(CLK_TCK)
39 import System.IO.Unsafe (unsafePerformIO)
40 #endif
41
42 #include "HsBaseConfig.h"
43
44 -- For _SC_CLK_TCK
45 #if HAVE_UNISTD_H
46 #include <unistd.h>
47 #endif
48
49 -- For struct rusage
50 #if !defined(mingw32_HOST_OS) && !defined(irix_HOST_OS)
51 # if HAVE_SYS_RESOURCE_H
52 #  include <sys/resource.h>
53 # endif
54 #endif
55
56 -- For FILETIME etc. on Windows
57 #if HAVE_WINDOWS_H
58 #include <windows.h>
59 #endif
60
61 -- for CLK_TCK
62 #if HAVE_TIME_H
63 #include <time.h>
64 #endif
65
66 -- for struct tms
67 #if HAVE_SYS_TIMES_H
68 #include <sys/times.h>
69 #endif
70
71 #endif
72
73 #if !defined(mingw32_HOST_OS) && !defined(cygwin32_HOST_OS)
74 realToInteger :: Real a => a -> Integer
75 realToInteger ct = round (realToFrac ct :: Double)
76   -- CTime, CClock, CUShort etc are in Real but not Fractional, 
77   -- so we must convert to Double before we can round it
78 #endif
79
80 #ifdef __GLASGOW_HASKELL__
81 -- -----------------------------------------------------------------------------
82 -- |Computation 'getCPUTime' returns the number of picoseconds CPU time
83 -- used by the current program.  The precision of this result is
84 -- implementation-dependent.
85
86 getCPUTime :: IO Integer
87 getCPUTime = do
88
89 #if !defined(mingw32_HOST_OS) && !defined(cygwin32_HOST_OS)
90 -- getrusage() is right royal pain to deal with when targetting multiple
91 -- versions of Solaris, since some versions supply it in libc (2.3 and 2.5),
92 -- while 2.4 has got it in libucb (I wouldn't be too surprised if it was back
93 -- again in libucb in 2.6..)
94 --
95 -- Avoid the problem by resorting to times() instead.
96 --
97 #if defined(HAVE_GETRUSAGE) && ! irix_HOST_OS && ! solaris2_HOST_OS
98     allocaBytes (#const sizeof(struct rusage)) $ \ p_rusage -> do
99     throwErrnoIfMinus1_ "getrusage" $ getrusage (#const RUSAGE_SELF) p_rusage
100
101     let ru_utime = (#ptr struct rusage, ru_utime) p_rusage
102     let ru_stime = (#ptr struct rusage, ru_stime) p_rusage
103     u_sec  <- (#peek struct timeval,tv_sec)  ru_utime :: IO CTime
104     u_usec <- (#peek struct timeval,tv_usec) ru_utime :: IO CSUSeconds
105     s_sec  <- (#peek struct timeval,tv_sec)  ru_stime :: IO CTime
106     s_usec <- (#peek struct timeval,tv_usec) ru_stime :: IO CSUSeconds
107     return ((realToInteger u_sec * 1000000 + realToInteger u_usec + 
108              realToInteger s_sec * 1000000 + realToInteger s_usec) 
109                 * 1000000)
110
111 type CRUsage = ()
112 foreign import ccall unsafe getrusage :: CInt -> Ptr CRUsage -> IO CInt
113 #else
114 # if defined(HAVE_TIMES)
115     allocaBytes (#const sizeof(struct tms)) $ \ p_tms -> do
116     _ <- times p_tms
117     u_ticks  <- (#peek struct tms,tms_utime) p_tms :: IO CClock
118     s_ticks  <- (#peek struct tms,tms_stime) p_tms :: IO CClock
119     return (( (realToInteger u_ticks + realToInteger s_ticks) * 1000000000000) 
120                         `div` fromIntegral clockTicks)
121
122 type CTms = ()
123 foreign import ccall unsafe times :: Ptr CTms -> IO CClock
124 # else
125     ioException (IOError Nothing UnsupportedOperation 
126                          "getCPUTime"
127                          "can't get CPU time"
128                          Nothing)
129 # endif
130 #endif
131
132 #else /* win32 */
133      -- NOTE: GetProcessTimes() is only supported on NT-based OSes.
134      -- The counts reported by GetProcessTimes() are in 100-ns (10^-7) units.
135     allocaBytes (#const sizeof(FILETIME)) $ \ p_creationTime -> do
136     allocaBytes (#const sizeof(FILETIME)) $ \ p_exitTime -> do
137     allocaBytes (#const sizeof(FILETIME)) $ \ p_kernelTime -> do
138     allocaBytes (#const sizeof(FILETIME)) $ \ p_userTime -> do
139     pid <- getCurrentProcess
140     ok <- getProcessTimes pid p_creationTime p_exitTime p_kernelTime p_userTime
141     if toBool ok then do
142       ut <- ft2psecs p_userTime
143       kt <- ft2psecs p_kernelTime
144       return (ut + kt)
145      else return 0
146   where 
147         ft2psecs :: Ptr FILETIME -> IO Integer
148         ft2psecs ft = do
149           high <- (#peek FILETIME,dwHighDateTime) ft :: IO Word32
150           low  <- (#peek FILETIME,dwLowDateTime)  ft :: IO Word32
151             -- Convert 100-ns units to picosecs (10^-12) 
152             -- => multiply by 10^5.
153           return (((fromIntegral high) * (2^(32::Int)) + (fromIntegral low)) * 100000)
154
155     -- ToDo: pin down elapsed times to just the OS thread(s) that
156     -- are evaluating/managing Haskell code.
157
158 type FILETIME = ()
159 type HANDLE = ()
160 -- need proper Haskell names (initial lower-case character)
161 foreign import stdcall unsafe "GetCurrentProcess" getCurrentProcess :: IO (Ptr HANDLE)
162 foreign import stdcall unsafe "GetProcessTimes" getProcessTimes :: Ptr HANDLE -> Ptr FILETIME -> Ptr FILETIME -> Ptr FILETIME -> Ptr FILETIME -> IO CInt
163
164 #endif /* not _WIN32 */
165 #endif /* __GLASGOW_HASKELL__ */
166
167 -- |The 'cpuTimePrecision' constant is the smallest measurable difference
168 -- in CPU time that the implementation can record, and is given as an
169 -- integral number of picoseconds.
170
171 #ifndef __NHC__
172 cpuTimePrecision :: Integer
173 cpuTimePrecision = round ((1000000000000::Integer) % fromIntegral (clockTicks))
174 #endif
175
176 #ifdef __GLASGOW_HASKELL__
177 clockTicks :: Int
178 clockTicks =
179 #if defined(CLK_TCK)
180     (#const CLK_TCK)
181 #else
182     unsafePerformIO (sysconf (#const _SC_CLK_TCK) >>= return . fromIntegral)
183 foreign import ccall unsafe sysconf :: CInt -> IO CLong
184 #endif
185 #endif /* __GLASGOW_HASKELL__ */