Inline more default methods
authorsimonpj@microsoft.com <unknown>
Thu, 29 Oct 2009 13:53:30 +0000 (13:53 +0000)
committersimonpj@microsoft.com <unknown>
Thu, 29 Oct 2009 13:53:30 +0000 (13:53 +0000)
Namely Monad: (>>)
       Eq:    (==), (/=)
       Num:   (-), negate
       Real:  quot, rem, div, mod, recip, (/), truncate
       Float: (**), logBase, sqrt, tan, tanh

GHC/Base.lhs
GHC/Classes.hs
GHC/Float.lhs
GHC/Num.lhs
GHC/Real.lhs

index 6293c12..401c157 100644 (file)
@@ -224,6 +224,7 @@ class  Monad m  where
     -- failure in a @do@ expression.
     fail        :: String -> m a
 
+    {-# INLINE (>>) #-}
     m >> k      = m >>= \_ -> k
     fail s      = error s
 \end{code}
index 1638456..3e0ec7a 100644 (file)
@@ -36,6 +36,8 @@ default ()              -- Double isn't available yet
 class  Eq a  where
     (==), (/=)           :: a -> a -> Bool
 
+    {-# INLINE (/=) #-}
+    {-# INLINE (==) #-}
     x /= y               = not (x == y)
     x == y               = not (x /= y)
 
index 9249507..9a4d4d9 100644 (file)
@@ -57,6 +57,11 @@ class  (Fractional a) => Floating a  where
     sinh, cosh, tanh    :: a -> a
     asinh, acosh, atanh :: a -> a
 
+    {-# INLINE (**) #-}
+    {-# INLINE logBase #-}
+    {-# INLINE sqrt #-}
+    {-# INLINE tan #-}
+    {-# INLINE tanh #-}
     x ** y              =  exp (log x * y)
     logBase x y         =  log y / log x
     sqrt x              =  x ** 0.5
index 19514b6..bfc5458 100644 (file)
@@ -75,6 +75,8 @@ class  (Eq a, Show a) => Num a  where
     -- so such literals have type @('Num' a) => a@.
     fromInteger         :: Integer -> a
 
+    {-# INLINE (-) #-}
+    {-# INLINE negate #-}
     x - y               = x + negate y
     negate x            = 0 - x
 
index fdce8b9..e830835 100644 (file)
@@ -133,10 +133,15 @@ class  (Real a, Enum a) => Integral a  where
     -- | conversion to 'Integer'
     toInteger           :: a -> Integer
 
+    {-# INLINE quot #-}
+    {-# INLINE rem #-}
+    {-# INLINE div #-}
+    {-# INLINE mod #-}
     n `quot` d          =  q  where (q,_) = quotRem n d
     n `rem` d           =  r  where (_,r) = quotRem n d
     n `div` d           =  q  where (q,_) = divMod n d
     n `mod` d           =  r  where (_,r) = divMod n d
+
     divMod n d          =  if signum r == negate (signum d) then (q-1, r+d) else qr
                            where qr@(q,r) = quotRem n d
 
@@ -154,6 +159,8 @@ class  (Num a) => Fractional a  where
     -- @('Fractional' a) => a@.
     fromRational        :: Rational -> a
 
+    {-# INLINE recip #-}
+    {-# INLINE (/) #-}
     recip x             =  1 / x
     x / y               = x * recip y
 
@@ -182,6 +189,7 @@ class  (Real a, Fractional a) => RealFrac a  where
     -- | @'floor' x@ returns the greatest integer not greater than @x@
     floor               :: (Integral b) => a -> b
 
+    {-# INLINE truncate #-}
     truncate x          =  m  where (m,_) = properFraction x
     
     round x             =  let (n,r) = properFraction x