Skip to content
Snippets Groups Projects
Commit 733d3362 authored by Simon Marlow's avatar Simon Marlow
Browse files

[project @ 1999-06-09 16:59:31 by simonmar]

Add a few SPECIALISE/INLINE pragmas.
parent d47f1285
No related branches found
No related tags found
No related merge requests found
......@@ -89,6 +89,8 @@ phase (x:+y) = atan2 y x
\begin{code}
instance (RealFloat a) => Num (Complex a) where
{-# SPECIALISE instance Num (Complex Float) #-}
{-# SPECIALISE instance Num (Complex Double) #-}
(x:+y) + (x':+y') = (x+x') :+ (y+y')
(x:+y) - (x':+y') = (x-x') :+ (y-y')
(x:+y) * (x':+y') = (x*x'-y*y') :+ (x*y'+y*x')
......@@ -99,6 +101,8 @@ instance (RealFloat a) => Num (Complex a) where
fromInteger n = fromInteger n :+ 0
instance (RealFloat a) => Fractional (Complex a) where
{-# SPECIALISE instance Fractional (Complex Float) #-}
{-# SPECIALISE instance Fractional (Complex Double) #-}
(x:+y) / (x':+y') = (x*x''+y*y'') / d :+ (y*x''-x*y'') / d
where x'' = scaleFloat k x'
y'' = scaleFloat k y'
......@@ -108,6 +112,8 @@ instance (RealFloat a) => Fractional (Complex a) where
fromRational a = fromRational a :+ 0
instance (RealFloat a) => Floating (Complex a) where
{-# SPECIALISE instance Floating (Complex Float) #-}
{-# SPECIALISE instance Floating (Complex Double) #-}
pi = pi :+ 0
exp (x:+y) = expx * cos y :+ expx * sin y
where expx = exp x
......
......@@ -61,7 +61,14 @@ instance Num Float where
signum x | x == 0.0 = 0
| x > 0.0 = 1
| otherwise = negate 1
{-# INLINE fromInteger #-}
fromInteger n = encodeFloat n 0
-- It's important that encodeFloat inlines here, and that
-- fromInteger in turn inlines,
-- so that if fromInteger is applied to an (S# i) the right thing happens
{-# INLINE fromInt #-}
fromInt i = int2Float i
instance Real Float where
......@@ -144,6 +151,7 @@ foreign import ccall "__encodeFloat" unsafe
foreign import ccall "__int_encodeFloat" unsafe
int_encodeFloat# :: Int# -> Int -> Float
foreign import ccall "isFloatNaN" unsafe isFloatNaN :: Float -> Int
foreign import ccall "isFloatInfinite" unsafe isFloatInfinite :: Float -> Int
foreign import ccall "isFloatDenormalized" unsafe isFloatDenormalized :: Float -> Int
......@@ -210,6 +218,9 @@ instance Num Double where
signum x | x == 0.0 = 0
| x > 0.0 = 1
| otherwise = negate 1
{-# INLINE fromInteger #-}
-- See comments with Num Float
fromInteger n = encodeFloat n 0
fromInt (I# n#) = case (int2Double# n#) of { d# -> D# d# }
......
......@@ -102,7 +102,9 @@ down the compilation chain to "see" the Num class.
\begin{code}
-- sum and product compute the sum or product of a finite list of numbers.
{-# SPECIALISE sum :: [Int] -> Int #-}
{-# SPECIALISE sum :: [Integer] -> Integer #-}
{-# SPECIALISE product :: [Int] -> Int #-}
{-# SPECIALISE product :: [Integer] -> Integer #-}
sum, product :: (Num a) => [a] -> a
#ifdef USE_REPORT_PRELUDE
sum = foldl (+) 0
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment