summaryrefslogtreecommitdiff
path: root/ghc/lib/std/CPUTime.lhs
blob: a695214a6dee1e3b8f001cf717ef29331328f7b1 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
% -----------------------------------------------------------------------------
% $Id: CPUTime.lhs,v 1.26 2001/01/11 07:04:16 qrczak Exp $
%
% (c) The University of Glasgow, 1995-2000
%
\section[CPUTime]{Haskell 98 CPU Time Library}

\begin{code}
{-# OPTIONS -#include "cbits/stgio.h" #-}

module CPUTime 
	(
         getCPUTime,       -- :: IO Integer
	 cpuTimePrecision  -- :: Integer
        ) where
\end{code}


#ifndef __HUGS__

\begin{code}
import Prelude		-- To generate the dependency
import PrelGHC		( indexIntArray# )
import PrelBase		( Int(..) )
import PrelByteArr  	( ByteArray(..), newIntArray )
import PrelArrExtra     ( unsafeFreezeByteArray )
import PrelNum		( fromInt )
import PrelIOBase	( IOError, IOException(..), 
			  IOErrorType( UnsupportedOperation ), 
			  unsafePerformIO, stToIO, ioException )
import Ratio
\end{code}

Computation @getCPUTime@ returns the number of picoseconds CPU time
used by the current program.  The precision of this result is
implementation-dependent.

The @cpuTimePrecision@ constant is the smallest measurable difference
in CPU time that the implementation can record, and is given as an
integral number of picoseconds.

\begin{code}
getCPUTime :: IO Integer
getCPUTime = do
    marr <- stToIO (newIntArray ((0::Int),3))
    barr <- stToIO (unsafeFreezeByteArray marr)
    rc   <- primGetCPUTime barr
    if rc /= 0 then
      case barr of
       ByteArray _ _ frozen# -> -- avoid bounds checking
        return ((fromIntegral (I# (indexIntArray# frozen# 0#)) * 1000000000 + 
                 fromIntegral (I# (indexIntArray# frozen# 1#)) + 
		 fromIntegral (I# (indexIntArray# frozen# 2#)) * 1000000000 + 
                 fromIntegral (I# (indexIntArray# frozen# 3#))) * 1000)
     else
	ioException (IOError Nothing UnsupportedOperation 
			 "getCPUTime"
		         "can't get CPU time"
			 Nothing)

cpuTimePrecision :: Integer
cpuTimePrecision = round ((1000000000000::Integer) % 
                          fromInt (unsafePerformIO clockTicks))

foreign import "libHS_cbits" "getCPUTime" unsafe primGetCPUTime :: ByteArray Int -> IO Int
foreign import "libHS_cbits" "clockTicks" unsafe clockTicks :: IO Int

\end{code}

#else

\begin{code}
import PrelPrim ( nh_getCPUtime
		, nh_getCPUprec
		, unsafePerformIO
		)

getCPUTime :: IO Integer
getCPUTime 
   = do seconds <- nh_getCPUtime
        return (round (seconds * 1.0e+12))

cpuTimePrecision :: Integer
cpuTimePrecision
   = unsafePerformIO (
        do resolution <- nh_getCPUprec
           return (round (resolution * 1.0e+12))
     )
\end{code} 
#endif