(original) (raw)
{-# LANGUAGE Trustworthy #-} {-# LANGUAGE BangPatterns , CPP , GHCForeignImportPrim , NoImplicitPrelude , MagicHash , UnboxedTuples , UnliftedFFITypes #-} {-# LANGUAGE CApiFFI #-}
{-# OPTIONS_GHC -Wno-orphans #-} {-# OPTIONS_HADDOCK not-home #-} {-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}
#include "ieee-flpt.h" #include "MachDeps.h"
#if WORD_SIZE_IN_BITS == 32
define WSHIFT 5
define MMASK 31
#elif WORD_SIZE_IN_BITS == 64
define WSHIFT 6
define MMASK 63
#else
error unsupported WORD_SIZE_IN_BITS
#endif
module GHC.Float ( module GHC.Float , Float(..), Double(..), Float#, Double# , double2Int, int2Double, float2Int, int2Float
import Data.Maybe
import GHC.Base import GHC.Bits import GHC.List import GHC.Enum import GHC.Show import GHC.Num import GHC.Real import GHC.Word import GHC.Arr import GHC.Float.RealFracMethods import GHC.Float.ConversionUtils import GHC.Num.BigNat
infixr 8 **
class (Fractional a) => Floating a where pi :: a exp, log, sqrt :: a -> a (**), logBase :: a -> a -> a sin, cos, tan :: a -> a asin, acos, atan :: a -> a sinh, cosh, tanh :: a -> a asinh, acosh, atanh :: a -> a
[log1p](GHC.Float.html#log1p) :: [a](#local-6989586621679544529) -> [a](#local-6989586621679544529)
[expm1](GHC.Float.html#expm1) :: [a](#local-6989586621679544529) -> [a](#local-6989586621679544529)
[log1pexp](GHC.Float.html#log1pexp) :: [a](#local-6989586621679544529) -> [a](#local-6989586621679544529)
[log1mexp](GHC.Float.html#log1mexp) :: [a](#local-6989586621679544529) -> [a](#local-6989586621679544529)
{-# INLINE (**) #-}
{-# INLINE [logBase](GHC.Float.html#logBase) #-}
{-# INLINE [sqrt](GHC.Float.html#sqrt) #-}
{-# INLINE [tan](GHC.Float.html#tan) #-}
{-# INLINE [tanh](GHC.Float.html#tanh) #-}
ax ** a y = a -> a forall a. Floating a => a -> a exp (a -> a forall a. Floating a => a -> a log a x a -> a -> a forall a. Num a => a -> a -> a * a y) logBase a x a y = a -> a forall a. Floating a => a -> a log a y a -> a -> a forall a. Fractional a => a -> a -> a / a -> a forall a. Floating a => a -> a log a x sqrt a x = a x a -> a -> a forall a. Floating a => a -> a -> a ** a 0.5 tan a x = a -> a forall a. Floating a => a -> a sin a x a -> a -> a forall a. Fractional a => a -> a -> a / a -> a forall a. Floating a => a -> a cos a x tanh a x = a -> a forall a. Floating a => a -> a sinh a x a -> a -> a forall a. Fractional a => a -> a -> a / a -> a forall a. Floating a => a -> a cosh a x
{-# INLINE [log1p](GHC.Float.html#log1p) #-}
{-# INLINE [expm1](GHC.Float.html#expm1) #-}
{-# INLINE [log1pexp](GHC.Float.html#log1pexp) #-}
{-# INLINE [log1mexp](GHC.Float.html#log1mexp) #-}
[log1p](GHC.Float.html#log1p) ax = a -> a forall a. Floating a => a -> a log (a 1 a -> a -> a forall a. Num a => a -> a -> a + a x) expm1 a x = a -> a forall a. Floating a => a -> a exp a x a -> a -> a forall a. Num a => a -> a -> a - a 1 log1pexp a x = a -> a forall a. Floating a => a -> a log1p (a -> a forall a. Floating a => a -> a exp a x) log1mexp a x = a -> a forall a. Floating a => a -> a log1p (a -> a forall a. Num a => a -> a negate (a -> a forall a. Floating a => a -> a exp a x))
log1mexpOrd :: (Ord a, Floating a) => a -> a {-# INLINE log1mexpOrd #-} log1mexpOrd :: forall a. (Ord a, Floating a) => a -> a log1mexpOrd a a | a a a -> a -> Bool forall a. Ord a => a -> a -> Bool > -(a -> a forall a. Floating a => a -> a log a 2) = a -> a forall a. Floating a => a -> a log (a -> a forall a. Num a => a -> a negate (a -> a forall a. Floating a => a -> a expm1 a a)) | Bool otherwise = a -> a forall a. Floating a => a -> a log1p (a -> a forall a. Num a => a -> a negate (a -> a forall a. Floating a => a -> a exp a a))
class (RealFrac a, Floating a) => RealFloat a where
[floatRadix](GHC.Float.html#floatRadix) :: [a](#local-6989586621679544523) -> [Integer](../../ghc-bignum-1.2/src/GHC-Num-Integer.html#Integer)
[floatDigits](GHC.Float.html#floatDigits) :: [a](#local-6989586621679544523) -> [Int](../../ghc-prim-0.8.0/src/GHC-Types.html#Int)
[floatRange](GHC.Float.html#floatRange) :: [a](#local-6989586621679544523) -> ([Int](../../ghc-prim-0.8.0/src/GHC-Types.html#Int),[Int](../../ghc-prim-0.8.0/src/GHC-Types.html#Int))
[decodeFloat](GHC.Float.html#decodeFloat) :: [a](#local-6989586621679544523) -> ([Integer](../../ghc-bignum-1.2/src/GHC-Num-Integer.html#Integer),[Int](../../ghc-prim-0.8.0/src/GHC-Types.html#Int))
[encodeFloat](GHC.Float.html#encodeFloat) :: [Integer](../../ghc-bignum-1.2/src/GHC-Num-Integer.html#Integer) -> [Int](../../ghc-prim-0.8.0/src/GHC-Types.html#Int) -> [a](#local-6989586621679544523)
[exponent](GHC.Float.html#exponent) :: [a](#local-6989586621679544523) -> [Int](../../ghc-prim-0.8.0/src/GHC-Types.html#Int)
[significand](GHC.Float.html#significand) :: [a](#local-6989586621679544523) -> [a](#local-6989586621679544523)
[scaleFloat](GHC.Float.html#scaleFloat) :: [Int](../../ghc-prim-0.8.0/src/GHC-Types.html#Int) -> [a](#local-6989586621679544523) -> [a](#local-6989586621679544523)
[isNaN](GHC.Float.html#isNaN) :: [a](#local-6989586621679544523) -> [Bool](../../ghc-prim-0.8.0/src/GHC-Types.html#Bool)
[isInfinite](GHC.Float.html#isInfinite) :: [a](#local-6989586621679544523) -> [Bool](../../ghc-prim-0.8.0/src/GHC-Types.html#Bool)
[isDenormalized](GHC.Float.html#isDenormalized) :: [a](#local-6989586621679544523) -> [Bool](../../ghc-prim-0.8.0/src/GHC-Types.html#Bool)
[isNegativeZero](GHC.Float.html#isNegativeZero) :: [a](#local-6989586621679544523) -> [Bool](../../ghc-prim-0.8.0/src/GHC-Types.html#Bool)
[isIEEE](GHC.Float.html#isIEEE) :: [a](#local-6989586621679544523) -> [Bool](../../ghc-prim-0.8.0/src/GHC-Types.html#Bool)
[atan2](GHC.Float.html#atan2) :: [a](#local-6989586621679544523) -> [a](#local-6989586621679544523) -> [a](#local-6989586621679544523)
[exponent](GHC.Float.html#exponent) ax = if Integer m Integer -> Integer -> Bool forall a. Eq a => a -> a -> Bool == Integer 0 then Int 0 else Int n Int -> Int -> Int forall a. Num a => a -> a -> a + a -> Int forall a. RealFloat a => a -> Int floatDigits a x where (Integer m,Int n) = a -> (Integer, Int) forall a. RealFloat a => a -> (Integer, Int) decodeFloat a x
[significand](GHC.Float.html#significand) ax = Integer -> Int -> a forall a. RealFloat a => Integer -> Int -> a encodeFloat Integer m (Int -> Int forall a. Num a => a -> a negate (a -> Int forall a. RealFloat a => a -> Int floatDigits a x)) where (Integer m,Int _) = a -> (Integer, Int) forall a. RealFloat a => a -> (Integer, Int) decodeFloat a x
[scaleFloat](GHC.Float.html#scaleFloat) Int0 a x = a x scaleFloat Int k a x | Bool isFix = a x | Bool otherwise = Integer -> Int -> a forall a. RealFloat a => Integer -> Int -> a encodeFloat Integer m (Int n Int -> Int -> Int forall a. Num a => a -> a -> a + Int -> Int -> Int clamp Int b Int k) where (Integer m,Int n) = a -> (Integer, Int) forall a. RealFloat a => a -> (Integer, Int) decodeFloat a x (Int l,Int h) = a -> (Int, Int) forall a. RealFloat a => a -> (Int, Int) floatRange a x d :: Int d = a -> Int forall a. RealFloat a => a -> Int floatDigits a x b :: Int b = Int h Int -> Int -> Int forall a. Num a => a -> a -> a - Int l Int -> Int -> Int forall a. Num a => a -> a -> a + Int 4Int -> Int -> Int forall a. Num a => a -> a -> a *Int d
isFix :: BoolisFix = a x a -> a -> Bool forall a. Eq a => a -> a -> Bool == a 0 Bool -> Bool -> Bool || a -> Bool forall a. RealFloat a => a -> Bool isNaN a x Bool -> Bool -> Bool || a -> Bool forall a. RealFloat a => a -> Bool isInfinite a x
[atan2](GHC.Float.html#atan2) ay a
x
| a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
0 = a -> a
forall a. Floating a => a -> a
atan (a
ya -> a -> a
forall a. Fractional a => a -> a -> a
/a
x)
| a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0 Bool -> Bool -> Bool
&& a
y a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
0 = a
forall a. Floating a => a
pia -> a -> a
forall a. Fractional a => a -> a -> a
/a
2
| a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0 Bool -> Bool -> Bool
&& a
y a -> a -> Bool
forall a. Ord a => a -> a -> Bool
> a
0 = a
forall a. Floating a => a
pi a -> a -> a
forall a. Num a => a -> a -> a
+ a -> a
forall a. Floating a => a -> a
atan (a
ya -> a -> a
forall a. Fractional a => a -> a -> a
/a
x)
|(a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
<= a
0 Bool -> Bool -> Bool
&& a
y a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0) Bool -> Bool -> Bool
||
(a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0 Bool -> Bool -> Bool
&& a -> Bool
forall a. RealFloat a => a -> Bool
isNegativeZero a
y) Bool -> Bool -> Bool
||
(a -> Bool
forall a. RealFloat a => a -> Bool
isNegativeZero a
x Bool -> Bool -> Bool
&& a -> Bool
forall a. RealFloat a => a -> Bool
isNegativeZero a
y)
= -a -> a -> a
forall a. RealFloat a => a -> a -> a
atan2 (-a
y) a
x
| a
y a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
0 Bool -> Bool -> Bool
&& (a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0 Bool -> Bool -> Bool
|| a -> Bool
forall a. RealFloat a => a -> Bool
isNegativeZero a
x)
= a
forall a. Floating a => a
pi
| a
xa -> a -> Bool
forall a. Eq a => a -> a -> Bool
==a
0 Bool -> Bool -> Bool
&& a
ya -> a -> Bool
forall a. Eq a => a -> a -> Bool
==a
0 = a
y
| Bool
otherwise = a
x a -> a -> a
forall a. Num a => a -> a -> a
+ a
y
instance Num Float where + :: Float -> Float -> Float (+) Float x Float y = Float -> Float -> Float plusFloat Float x Float y (-) Float x Float y = Float -> Float -> Float minusFloat Float x Float y negate :: Float -> Float negate Float x = Float -> Float negateFloat Float x * :: Float -> Float -> Float (*) Float x Float y = Float -> Float -> Float timesFloat Float x Float y abs :: Float -> Float abs Float x = Float -> Float fabsFloat Float x signum :: Float -> Float signum Float x | Float x Float -> Float -> Bool forall a. Ord a => a -> a -> Bool > Float 0 = Float 1 | Float x Float -> Float -> Bool forall a. Ord a => a -> a -> Bool < Float 0 = Float -> Float negateFloat Float 1 | Bool otherwise = Float x
{-# INLINE [fromInteger](GHC.Num.html#fromInteger) #-}
fromInteger :: Integer -> FloatfromInteger Integer i = Float# -> Float F# (Integer -> Float# integerToFloat# Integer i)
integerToFloat# :: Integer -> Float# {-# NOINLINE integerToFloat# #-} integerToFloat# :: Integer -> Float# integerToFloat# (IS Int# i) = Int# -> Float# int2Float# Int# i integerToFloat# i :: Integer i@(IP ByteArray# _) = case Integer -> Float forall a. RealFloat a => Integer -> a integerToBinaryFloat' Integer i of F# Float# x -> Float# x integerToFloat# (IN ByteArray# bn) = case Integer -> Float forall a. RealFloat a => Integer -> a integerToBinaryFloat' (ByteArray# -> Integer IP ByteArray# bn) of F# Float# x -> Float# -> Float# negateFloat# Float# x
naturalToFloat# :: Natural -> Float# {-# NOINLINE naturalToFloat# #-} naturalToFloat# :: Natural -> Float# naturalToFloat# (NS Word# w) = Word# -> Float# word2Float# Word# w naturalToFloat# (NB ByteArray# b) = case Integer -> Float forall a. RealFloat a => Integer -> a integerToBinaryFloat' (ByteArray# -> Integer IP ByteArray# b) of F# Float# x -> Float# x
instance Real Float where
toRational :: Float -> Rational
toRational (F# Float#
x#) =
case Float# -> (# Int#, Int# #)
decodeFloat_Int# Float#
x# of
(# Int#
m#, Int#
e# #)
| Int# -> Bool
isTrue# (Int#
e# Int# -> Int# -> Int#
>=# Int#
0#) ->
(Int# -> Integer
IS Int#
m# Integer -> Word# -> Integer
integerShiftL# Int# -> Word#
int2Word# Int#
e#) Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% Integer
1
| Int# -> Bool
isTrue# ((Int# -> Word#
int2Word# Int#
m# Word# -> Word# -> Word#
and# Word#
1##) Word# -> Word# -> Int#
eqWord# Word#
0##) ->
case Int# -> Int# -> (# Integer, Int# #)
elimZerosInt# Int#
m# (Int# -> Int#
negateInt# Int#
e#) of
(# Integer
n, Int#
d# #) -> Integer
n Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% Integer -> Word# -> Integer
integerShiftL# Integer
1 (Int# -> Word#
int2Word# Int#
d#)
| Bool
otherwise ->
Int# -> Integer
IS Int#
m# Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% Integer -> Word# -> Integer
integerShiftL# Integer
1 (Int# -> Word#
int2Word# (Int# -> Int#
negateInt# Int#
e#))
instance Fractional Float where / :: Float -> Float -> Float (/) Float x Float y = Float -> Float -> Float divideFloat Float x Float y {-# INLINE fromRational #-} fromRational :: Rational -> Float fromRational (Integer n:%Integer d) = Integer -> Integer -> Float rationalToFloat Integer n Integer d recip :: Float -> Float recip Float x = Float 1.0 Float -> Float -> Float forall a. Fractional a => a -> a -> a / Float x
rationalToFloat :: Integer -> Integer -> Float {-# NOINLINE [1] rationalToFloat #-} rationalToFloat :: Integer -> Integer -> Float rationalToFloat Integer n Integer 0 | Integer n Integer -> Integer -> Bool forall a. Eq a => a -> a -> Bool == Integer 0 = Float 0Float -> Float -> Float forall a. Fractional a => a -> a -> a /Float 0 | Integer n Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool < Integer 0 = (-Float 1)Float -> Float -> Float forall a. Fractional a => a -> a -> a /Float 0 | Bool otherwise = Float 1Float -> Float -> Float forall a. Fractional a => a -> a -> a /Float 0 rationalToFloat Integer n Integer d | Integer n Integer -> Integer -> Bool forall a. Eq a => a -> a -> Bool == Integer 0 = Integer -> Int -> Float forall a. RealFloat a => Integer -> Int -> a encodeFloat Integer 0 Int 0 | Integer n Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool < Integer 0 = -(Int -> Int -> Integer -> Integer -> Float forall a. RealFloat a => Int -> Int -> Integer -> Integer -> a fromRat'' Int minEx Int mantDigs (-Integer n) Integer d) | Bool otherwise = Int -> Int -> Integer -> Integer -> Float forall a. RealFloat a => Int -> Int -> Integer -> Integer -> a fromRat'' Int minEx Int mantDigs Integer n Integer d where minEx :: Int minEx = FLT_MIN_EXP mantDigs :: Int mantDigs = FLT_MANT_DIG
{-# RULES "properFraction/Float->Integer" properFraction = properFractionFloatInteger "truncate/Float->Integer" truncate = truncateFloatInteger "floor/Float->Integer" floor = floorFloatInteger "ceiling/Float->Integer" ceiling = ceilingFloatInteger "round/Float->Integer" round = roundFloatInteger "properFraction/Float->Int" properFraction = properFractionFloatInt "truncate/Float->Int" truncate = float2Int "floor/Float->Int" floor = floorFloatInt "ceiling/Float->Int" ceiling = ceilingFloatInt "round/Float->Int" round = roundFloatInt #-}
{-# INLINE [1] [ceiling](GHC.Real.html#ceiling) #-}
{-# INLINE [1] [floor](GHC.Real.html#floor) #-}
{-# INLINE [1] [truncate](GHC.Real.html#truncate) #-}#if FLT_RADIX != 2
#error FLT_RADIX must be 2
#endif
properFraction :: forall b. Integral b => Float -> (b, Float)
properFraction (F# Float#
x#)
= case Float# -> (# Int#, Int# #)
decodeFloat_Int# Float#
x# of
(# Int#
m#, Int#
n# #) ->
let m :: Int
m = Int# -> Int
I# Int#
m#
n :: Int
n = Int# -> Int
I# Int#
n#
in
if Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0
then (Int -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
m b -> b -> b
forall a. Num a => a -> a -> a
* (b
2 b -> Int -> b
forall a b. (Num a, Integral b) => a -> b -> a
^ Int
n), Float
0.0)
else let i :: Int
i = if Int
m Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 then Int
m Int -> Int -> Int
forall a. Bits a => a -> Int -> a
shiftR Int -> Int
forall a. Num a => a -> a
negate Int
n
else Int -> Int
forall a. Num a => a -> a
negate (Int -> Int
forall a. Num a => a -> a
negate Int
m Int -> Int -> Int
forall a. Bits a => a -> Int -> a
shiftR Int -> Int
forall a. Num a => a -> a
negate Int
n)
f :: Int
f = Int
m Int -> Int -> Int
forall a. Num a => a -> a -> a
- (Int
i Int -> Int -> Int
forall a. Bits a => a -> Int -> a
shiftL Int -> Int
forall a. Num a => a -> a
negate Int
n)
in (Int -> b
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
i, Integer -> Int -> Float
forall a. RealFloat a => Integer -> Int -> a
encodeFloat (Int -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
f) Int
n)
truncate :: forall b. Integral b => Float -> btruncate Float x = case Float -> (b, Float) forall a b. (RealFrac a, Integral b) => a -> (b, a) properFraction Float x of (b n,Float _) -> b n
round :: forall b. Integral b => Float -> bround Float x = case Float -> (b, Float) forall a b. (RealFrac a, Integral b) => a -> (b, a) properFraction Float x of (b n,Float r) -> let m :: b m = if Float r Float -> Float -> Bool forall a. Ord a => a -> a -> Bool < Float 0.0 then b n b -> b -> b forall a. Num a => a -> a -> a - b 1 else b n b -> b -> b forall a. Num a => a -> a -> a + b 1 half_down :: Float half_down = Float -> Float forall a. Num a => a -> a abs Float r Float -> Float -> Float forall a. Num a => a -> a -> a - Float 0.5 in case (Float -> Float -> Ordering forall a. Ord a => a -> a -> Ordering compare Float half_down Float 0.0) of Ordering LT -> b n Ordering EQ -> if b -> Bool forall a. Integral a => a -> Bool even b n then b n else b m Ordering GT -> b m
ceiling :: forall b. Integral b => Float -> bceiling Float x = case Float -> (b, Float) forall a b. (RealFrac a, Integral b) => a -> (b, a) properFraction Float x of (b n,Float r) -> if Float r Float -> Float -> Bool forall a. Ord a => a -> a -> Bool > Float 0.0 then b n b -> b -> b forall a. Num a => a -> a -> a + b 1 else b n
floor :: forall b. Integral b => Float -> bfloor Float x = case Float -> (b, Float) forall a b. (RealFrac a, Integral b) => a -> (b, a) properFraction Float x of (b n,Float r) -> if Float r Float -> Float -> Bool forall a. Ord a => a -> a -> Bool < Float 0.0 then b n b -> b -> b forall a. Num a => a -> a -> a - b 1 else b n
instance Floating Float where pi :: Float pi = Float 3.141592653589793238 exp :: Float -> Float exp Float x = Float -> Float expFloat Float x log :: Float -> Float log Float x = Float -> Float logFloat Float x sqrt :: Float -> Float sqrt Float x = Float -> Float sqrtFloat Float x sin :: Float -> Float sin Float x = Float -> Float sinFloat Float x cos :: Float -> Float cos Float x = Float -> Float cosFloat Float x tan :: Float -> Float tan Float x = Float -> Float tanFloat Float x asin :: Float -> Float asin Float x = Float -> Float asinFloat Float x acos :: Float -> Float acos Float x = Float -> Float acosFloat Float x atan :: Float -> Float atan Float x = Float -> Float atanFloat Float x sinh :: Float -> Float sinh Float x = Float -> Float sinhFloat Float x cosh :: Float -> Float cosh Float x = Float -> Float coshFloat Float x tanh :: Float -> Float tanh Float x = Float -> Float tanhFloat Float x ** :: Float -> Float -> Float (**) Float x Float y = Float -> Float -> Float powerFloat Float x Float y logBase :: Float -> Float -> Float logBase Float x Float y = Float -> Float forall a. Floating a => a -> a log Float y Float -> Float -> Float forall a. Fractional a => a -> a -> a / Float -> Float forall a. Floating a => a -> a log Float x
asinh :: Float -> Floatasinh Float x = Float -> Float asinhFloat Float x acosh :: Float -> Float acosh Float x = Float -> Float acoshFloat Float x atanh :: Float -> Float atanh Float x = Float -> Float atanhFloat Float x
log1p :: Float -> Floatlog1p = Float -> Float log1pFloat expm1 :: Float -> Float expm1 = Float -> Float expm1Float
log1mexp :: Float -> Floatlog1mexp Float x = Float -> Float forall a. (Ord a, Floating a) => a -> a log1mexpOrd Float x {-# INLINE log1mexp #-} log1pexp :: Float -> Float log1pexp Float a | Float a Float -> Float -> Bool forall a. Ord a => a -> a -> Bool <= Float 18 = Float -> Float log1pFloat (Float -> Float forall a. Floating a => a -> a exp Float a) | Float a Float -> Float -> Bool forall a. Ord a => a -> a -> Bool <= Float 100 = Float a Float -> Float -> Float forall a. Num a => a -> a -> a + Float -> Float forall a. Floating a => a -> a exp (Float -> Float forall a. Num a => a -> a negate Float a) | Bool otherwise = Float a {-# INLINE log1pexp #-}
instance RealFloat Float where
floatRadix :: Float -> Integer
floatRadix Float
_ = FLT_RADIX
floatDigits :: Float -> Int
floatDigits Float
_ = FLT_MANT_DIG
floatRange :: Float -> (Int, Int)
floatRange Float
_ = (FLT_MIN_EXP, FLT_MAX_EXP)
decodeFloat :: Float -> (Integer, Int)decodeFloat (F# Float# f#) = case Float# -> (# Int#, Int# #) decodeFloat_Int# Float# f# of (# Int# i, Int# e #) -> (Int# -> Integer IS Int# i, Int# -> Int I# Int# e)
encodeFloat :: Integer -> Int -> FloatencodeFloat Integer i (I# Int# e) = Float# -> Float F# (Integer -> Int# -> Float# integerEncodeFloat# Integer i Int# e)
exponent :: Float -> Intexponent Float x = case Float -> (Integer, Int) forall a. RealFloat a => a -> (Integer, Int) decodeFloat Float x of (Integer m,Int n) -> if Integer m Integer -> Integer -> Bool forall a. Eq a => a -> a -> Bool == Integer 0 then Int 0 else Int n Int -> Int -> Int forall a. Num a => a -> a -> a + Float -> Int forall a. RealFloat a => a -> Int floatDigits Float x
significand :: Float -> Floatsignificand Float x = case Float -> (Integer, Int) forall a. RealFloat a => a -> (Integer, Int) decodeFloat Float x of (Integer m,Int _) -> Integer -> Int -> Float forall a. RealFloat a => Integer -> Int -> a encodeFloat Integer m (Int -> Int forall a. Num a => a -> a negate (Float -> Int forall a. RealFloat a => a -> Int floatDigits Float x))
scaleFloat :: Int -> Float -> FloatscaleFloat Int 0 Float x = Float x scaleFloat Int k Float x | Bool isFix = Float x | Bool otherwise = case Float -> (Integer, Int) forall a. RealFloat a => a -> (Integer, Int) decodeFloat Float x of (Integer m,Int n) -> Integer -> Int -> Float forall a. RealFloat a => Integer -> Int -> a encodeFloat Integer m (Int n Int -> Int -> Int forall a. Num a => a -> a -> a + Int -> Int -> Int clamp Int bf Int k) where bf :: Int bf = FLT_MAX_EXP - (FLT_MIN_EXP) + 4*FLT_MANT_DIG isFix :: Bool isFix = Float x Float -> Float -> Bool forall a. Eq a => a -> a -> Bool == Float 0 Bool -> Bool -> Bool || Float -> Int isFloatFinite Float x Int -> Int -> Bool forall a. Eq a => a -> a -> Bool == Int 0
isNaN :: Float -> BoolisNaN Float x = Int 0 Int -> Int -> Bool forall a. Eq a => a -> a -> Bool /= Float -> Int isFloatNaN Float x isInfinite :: Float -> Bool isInfinite Float x = Int 0 Int -> Int -> Bool forall a. Eq a => a -> a -> Bool /= Float -> Int isFloatInfinite Float x isDenormalized :: Float -> Bool isDenormalized Float x = Int 0 Int -> Int -> Bool forall a. Eq a => a -> a -> Bool /= Float -> Int isFloatDenormalized Float x isNegativeZero :: Float -> Bool isNegativeZero Float x = Int 0 Int -> Int -> Bool forall a. Eq a => a -> a -> Bool /= Float -> Int isFloatNegativeZero Float x isIEEE :: Float -> Bool isIEEE Float _ = Bool True
instance Show Float where showsPrec :: Int -> Float -> ShowS showsPrec Int x = (Float -> ShowS) -> Int -> Float -> ShowS forall a. RealFloat a => (a -> ShowS) -> Int -> a -> ShowS showSignedFloat Float -> ShowS forall a. RealFloat a => a -> ShowS showFloat Int x showList :: [Float] -> ShowS showList = (Float -> ShowS) -> [Float] -> ShowS forall a. (a -> ShowS) -> [a] -> ShowS showList__ (Int -> Float -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int 0)
instance Num Double where + :: Double -> Double -> Double (+) Double x Double y = Double -> Double -> Double plusDouble Double x Double y (-) Double x Double y = Double -> Double -> Double minusDouble Double x Double y negate :: Double -> Double negate Double x = Double -> Double negateDouble Double x * :: Double -> Double -> Double (*) Double x Double y = Double -> Double -> Double timesDouble Double x Double y abs :: Double -> Double abs Double x = Double -> Double fabsDouble Double x signum :: Double -> Double signum Double x | Double x Double -> Double -> Bool forall a. Ord a => a -> a -> Bool > Double 0 = Double 1 | Double x Double -> Double -> Bool forall a. Ord a => a -> a -> Bool < Double 0 = Double -> Double negateDouble Double 1 | Bool otherwise = Double x
{-# INLINE [fromInteger](GHC.Num.html#fromInteger) #-}
fromInteger :: Integer -> DoublefromInteger Integer i = Double# -> Double D# (Integer -> Double# integerToDouble# Integer i)
integerToDouble# :: Integer -> Double# {-# NOINLINE integerToDouble# #-} integerToDouble# :: Integer -> Double# integerToDouble# (IS Int# i) = Int# -> Double# int2Double# Int# i integerToDouble# i :: Integer i@(IP ByteArray# _) = case Integer -> Double forall a. RealFloat a => Integer -> a integerToBinaryFloat' Integer i of D# Double# x -> Double# x integerToDouble# (IN ByteArray# bn) = case Integer -> Double forall a. RealFloat a => Integer -> a integerToBinaryFloat' (ByteArray# -> Integer IP ByteArray# bn) of D# Double# x -> Double# -> Double# negateDouble# Double# x
naturalToDouble# :: Natural -> Double# {-# NOINLINE naturalToDouble# #-} naturalToDouble# :: Natural -> Double# naturalToDouble# (NS Word# w) = Word# -> Double# word2Double# Word# w naturalToDouble# (NB ByteArray# b) = case Integer -> Double forall a. RealFloat a => Integer -> a integerToBinaryFloat' (ByteArray# -> Integer IP ByteArray# b) of D# Double# x -> Double# x
instance Real Double where
toRational :: Double -> Rational
toRational (D# Double#
x#) =
case Double# -> (# Integer, Int# #)
integerDecodeDouble# Double#
x# of
(# Integer
m, Int#
e# #)
| Int# -> Bool
isTrue# (Int#
e# Int# -> Int# -> Int#
>=# Int#
0#) ->
Integer -> Word# -> Integer
integerShiftL# Integer
m (Int# -> Word#
int2Word# Int#
e#) Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% Integer
1
| Int# -> Bool
isTrue# ((Integer -> Word#
integerToWord# Integer
m Word# -> Word# -> Word#
and# Word#
1##) Word# -> Word# -> Int#
eqWord# Word#
0##) ->
case Integer -> Int# -> (# Integer, Int# #)
elimZerosInteger Integer
m (Int# -> Int#
negateInt# Int#
e#) of
(# Integer
n, Int#
d# #) -> Integer
n Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% Integer -> Word# -> Integer
integerShiftL# Integer
1 (Int# -> Word#
int2Word# Int#
d#)
| Bool
otherwise ->
Integer
m Integer -> Integer -> Rational
forall a. a -> a -> Ratio a
:% Integer -> Word# -> Integer
integerShiftL# Integer
1 (Int# -> Word#
int2Word# (Int# -> Int#
negateInt# Int#
e#))
instance Fractional Double where / :: Double -> Double -> Double (/) Double x Double y = Double -> Double -> Double divideDouble Double x Double y {-# INLINE fromRational #-} fromRational :: Rational -> Double fromRational (Integer n:%Integer d) = Integer -> Integer -> Double rationalToDouble Integer n Integer d recip :: Double -> Double recip Double x = Double 1.0 Double -> Double -> Double forall a. Fractional a => a -> a -> a / Double x
rationalToDouble :: Integer -> Integer -> Double {-# NOINLINE [1] rationalToDouble #-} rationalToDouble :: Integer -> Integer -> Double rationalToDouble Integer n Integer 0 | Integer n Integer -> Integer -> Bool forall a. Eq a => a -> a -> Bool == Integer 0 = Double 0Double -> Double -> Double forall a. Fractional a => a -> a -> a /Double 0 | Integer n Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool < Integer 0 = (-Double 1)Double -> Double -> Double forall a. Fractional a => a -> a -> a /Double 0 | Bool otherwise = Double 1Double -> Double -> Double forall a. Fractional a => a -> a -> a /Double 0 rationalToDouble Integer n Integer d | Integer n Integer -> Integer -> Bool forall a. Eq a => a -> a -> Bool == Integer 0 = Integer -> Int -> Double forall a. RealFloat a => Integer -> Int -> a encodeFloat Integer 0 Int 0 | Integer n Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool < Integer 0 = -(Int -> Int -> Integer -> Integer -> Double forall a. RealFloat a => Int -> Int -> Integer -> Integer -> a fromRat'' Int minEx Int mantDigs (-Integer n) Integer d) | Bool otherwise = Int -> Int -> Integer -> Integer -> Double forall a. RealFloat a => Int -> Int -> Integer -> Integer -> a fromRat'' Int minEx Int mantDigs Integer n Integer d where minEx :: Int minEx = DBL_MIN_EXP mantDigs :: Int mantDigs = DBL_MANT_DIG
instance Floating Double where pi :: Double pi = Double 3.141592653589793238 exp :: Double -> Double exp Double x = Double -> Double expDouble Double x log :: Double -> Double log Double x = Double -> Double logDouble Double x sqrt :: Double -> Double sqrt Double x = Double -> Double sqrtDouble Double x sin :: Double -> Double sin Double x = Double -> Double sinDouble Double x cos :: Double -> Double cos Double x = Double -> Double cosDouble Double x tan :: Double -> Double tan Double x = Double -> Double tanDouble Double x asin :: Double -> Double asin Double x = Double -> Double asinDouble Double x acos :: Double -> Double acos Double x = Double -> Double acosDouble Double x atan :: Double -> Double atan Double x = Double -> Double atanDouble Double x sinh :: Double -> Double sinh Double x = Double -> Double sinhDouble Double x cosh :: Double -> Double cosh Double x = Double -> Double coshDouble Double x tanh :: Double -> Double tanh Double x = Double -> Double tanhDouble Double x ** :: Double -> Double -> Double (**) Double x Double y = Double -> Double -> Double powerDouble Double x Double y logBase :: Double -> Double -> Double logBase Double x Double y = Double -> Double forall a. Floating a => a -> a log Double y Double -> Double -> Double forall a. Fractional a => a -> a -> a / Double -> Double forall a. Floating a => a -> a log Double x
asinh :: Double -> Doubleasinh Double x = Double -> Double asinhDouble Double x acosh :: Double -> Double acosh Double x = Double -> Double acoshDouble Double x atanh :: Double -> Double atanh Double x = Double -> Double atanhDouble Double x
log1p :: Double -> Doublelog1p = Double -> Double log1pDouble expm1 :: Double -> Double expm1 = Double -> Double expm1Double
log1mexp :: Double -> Doublelog1mexp Double x = Double -> Double forall a. (Ord a, Floating a) => a -> a log1mexpOrd Double x {-# INLINE log1mexp #-} log1pexp :: Double -> Double log1pexp Double a | Double a Double -> Double -> Bool forall a. Ord a => a -> a -> Bool <= Double 18 = Double -> Double log1pDouble (Double -> Double forall a. Floating a => a -> a exp Double a) | Double a Double -> Double -> Bool forall a. Ord a => a -> a -> Bool <= Double 100 = Double a Double -> Double -> Double forall a. Num a => a -> a -> a + Double -> Double forall a. Floating a => a -> a exp (Double -> Double forall a. Num a => a -> a negate Double a) | Bool otherwise = Double a {-# INLINE log1pexp #-}
{-# RULES "properFraction/Double->Integer" properFraction = properFractionDoubleInteger "truncate/Double->Integer" truncate = truncateDoubleInteger "floor/Double->Integer" floor = floorDoubleInteger "ceiling/Double->Integer" ceiling = ceilingDoubleInteger "round/Double->Integer" round = roundDoubleInteger "properFraction/Double->Int" properFraction = properFractionDoubleInt "truncate/Double->Int" truncate = double2Int "floor/Double->Int" floor = floorDoubleInt "ceiling/Double->Int" ceiling = ceilingDoubleInt "round/Double->Int" round = roundDoubleInt #-}
instance RealFrac Double where
{-# INLINE [1] [ceiling](GHC.Real.html#ceiling) #-}
{-# INLINE [1] [floor](GHC.Real.html#floor) #-}
{-# INLINE [1] [truncate](GHC.Real.html#truncate) #-}
properFraction :: forall b. Integral b => Double -> (b, Double)properFraction Double x = case (Double -> (Integer, Int) forall a. RealFloat a => a -> (Integer, Int) decodeFloat Double x) of { (Integer m,Int n) -> if Int n Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >= Int 0 then (Integer -> b forall a. Num a => Integer -> a fromInteger Integer m b -> b -> b forall a. Num a => a -> a -> a * b 2 b -> Int -> b forall a b. (Num a, Integral b) => a -> b -> a ^ Int n, Double 0.0) else case (Integer -> Integer -> (Integer, Integer) forall a. Integral a => a -> a -> (a, a) quotRem Integer m (Integer 2Integer -> Int -> Integer forall a b. (Num a, Integral b) => a -> b -> a ^(Int -> Int forall a. Num a => a -> a negate Int n))) of { (Integer w,Integer r) -> (Integer -> b forall a. Num a => Integer -> a fromInteger Integer w, Integer -> Int -> Double forall a. RealFloat a => Integer -> Int -> a encodeFloat Integer r Int n) } }
truncate :: forall b. Integral b => Double -> btruncate Double x = case Double -> (b, Double) forall a b. (RealFrac a, Integral b) => a -> (b, a) properFraction Double x of (b n,Double _) -> b n
round :: forall b. Integral b => Double -> bround Double x = case Double -> (b, Double) forall a b. (RealFrac a, Integral b) => a -> (b, a) properFraction Double x of (b n,Double r) -> let m :: b m = if Double r Double -> Double -> Bool forall a. Ord a => a -> a -> Bool < Double 0.0 then b n b -> b -> b forall a. Num a => a -> a -> a - b 1 else b n b -> b -> b forall a. Num a => a -> a -> a + b 1 half_down :: Double half_down = Double -> Double forall a. Num a => a -> a abs Double r Double -> Double -> Double forall a. Num a => a -> a -> a - Double 0.5 in case (Double -> Double -> Ordering forall a. Ord a => a -> a -> Ordering compare Double half_down Double 0.0) of Ordering LT -> b n Ordering EQ -> if b -> Bool forall a. Integral a => a -> Bool even b n then b n else b m Ordering GT -> b m
ceiling :: forall b. Integral b => Double -> bceiling Double x = case Double -> (b, Double) forall a b. (RealFrac a, Integral b) => a -> (b, a) properFraction Double x of (b n,Double r) -> if Double r Double -> Double -> Bool forall a. Ord a => a -> a -> Bool > Double 0.0 then b n b -> b -> b forall a. Num a => a -> a -> a + b 1 else b n
floor :: forall b. Integral b => Double -> bfloor Double x = case Double -> (b, Double) forall a b. (RealFrac a, Integral b) => a -> (b, a) properFraction Double x of (b n,Double r) -> if Double r Double -> Double -> Bool forall a. Ord a => a -> a -> Bool < Double 0.0 then b n b -> b -> b forall a. Num a => a -> a -> a - b 1 else b n
instance RealFloat Double where
floatRadix :: Double -> Integer
floatRadix Double
_ = FLT_RADIX
floatDigits :: Double -> Int
floatDigits Double
_ = DBL_MANT_DIG
floatRange :: Double -> (Int, Int)
floatRange Double
_ = (DBL_MIN_EXP, DBL_MAX_EXP)
decodeFloat :: Double -> (Integer, Int)decodeFloat (D# Double# x#) = case Double# -> (# Integer, Int# #) integerDecodeDouble# Double# x# of (# Integer i, Int# j #) -> (Integer i, Int# -> Int I# Int# j)
encodeFloat :: Integer -> Int -> DoubleencodeFloat Integer i (I# Int# j) = Double# -> Double D# (Integer -> Int# -> Double# integerEncodeDouble# Integer i Int# j)
exponent :: Double -> Intexponent Double x = case Double -> (Integer, Int) forall a. RealFloat a => a -> (Integer, Int) decodeFloat Double x of (Integer m,Int n) -> if Integer m Integer -> Integer -> Bool forall a. Eq a => a -> a -> Bool == Integer 0 then Int 0 else Int n Int -> Int -> Int forall a. Num a => a -> a -> a + Double -> Int forall a. RealFloat a => a -> Int floatDigits Double x
significand :: Double -> Doublesignificand Double x = case Double -> (Integer, Int) forall a. RealFloat a => a -> (Integer, Int) decodeFloat Double x of (Integer m,Int _) -> Integer -> Int -> Double forall a. RealFloat a => Integer -> Int -> a encodeFloat Integer m (Int -> Int forall a. Num a => a -> a negate (Double -> Int forall a. RealFloat a => a -> Int floatDigits Double x))
scaleFloat :: Int -> Double -> DoublescaleFloat Int 0 Double x = Double x scaleFloat Int k Double x | Bool isFix = Double x | Bool otherwise = case Double -> (Integer, Int) forall a. RealFloat a => a -> (Integer, Int) decodeFloat Double x of (Integer m,Int n) -> Integer -> Int -> Double forall a. RealFloat a => Integer -> Int -> a encodeFloat Integer m (Int n Int -> Int -> Int forall a. Num a => a -> a -> a + Int -> Int -> Int clamp Int bd Int k) where bd :: Int bd = DBL_MAX_EXP - (DBL_MIN_EXP) + 4*DBL_MANT_DIG isFix :: Bool isFix = Double x Double -> Double -> Bool forall a. Eq a => a -> a -> Bool == Double 0 Bool -> Bool -> Bool || Double -> Int isDoubleFinite Double x Int -> Int -> Bool forall a. Eq a => a -> a -> Bool == Int 0
isNaN :: Double -> BoolisNaN Double x = Int 0 Int -> Int -> Bool forall a. Eq a => a -> a -> Bool /= Double -> Int isDoubleNaN Double x isInfinite :: Double -> Bool isInfinite Double x = Int 0 Int -> Int -> Bool forall a. Eq a => a -> a -> Bool /= Double -> Int isDoubleInfinite Double x isDenormalized :: Double -> Bool isDenormalized Double x = Int 0 Int -> Int -> Bool forall a. Eq a => a -> a -> Bool /= Double -> Int isDoubleDenormalized Double x isNegativeZero :: Double -> Bool isNegativeZero Double x = Int 0 Int -> Int -> Bool forall a. Eq a => a -> a -> Bool /= Double -> Int isDoubleNegativeZero Double x isIEEE :: Double -> Bool isIEEE Double _ = Bool True
instance Show Double where showsPrec :: Int -> Double -> ShowS showsPrec Int x = (Double -> ShowS) -> Int -> Double -> ShowS forall a. RealFloat a => (a -> ShowS) -> Int -> a -> ShowS showSignedFloat Double -> ShowS forall a. RealFloat a => a -> ShowS showFloat Int x showList :: [Double] -> ShowS showList = (Double -> ShowS) -> [Double] -> ShowS forall a. (a -> ShowS) -> [a] -> ShowS showList__ (Int -> Double -> ShowS forall a. Show a => Int -> a -> ShowS showsPrec Int 0)
instance Enum Float where
succ :: Float -> Float
succ Float
x = Float
x Float -> Float -> Float
forall a. Num a => a -> a -> a
+ Float
1
pred :: Float -> Float
pred Float
x = Float
x Float -> Float -> Float
forall a. Num a => a -> a -> a
- Float
1
toEnum :: Int -> Float
toEnum = Int -> Float
int2Float
fromEnum :: Float -> Int
fromEnum = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Integer -> Int) -> (Float -> Integer) -> Float -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
truncate
enumFrom :: Float -> [Float]
enumFrom = Float -> [Float]
forall a. Fractional a => a -> [a]
numericEnumFrom
enumFromTo :: Float -> Float -> [Float]
enumFromTo = Float -> Float -> [Float]
forall a. (Ord a, Fractional a) => a -> a -> [a]
numericEnumFromTo
enumFromThen :: Float -> Float -> [Float]
enumFromThen = Float -> Float -> [Float]
forall a. Fractional a => a -> a -> [a]
numericEnumFromThen
enumFromThenTo :: Float -> Float -> Float -> [Float]
enumFromThenTo = Float -> Float -> Float -> [Float]
forall a. (Ord a, Fractional a) => a -> a -> a -> [a]
numericEnumFromThenTo
instance Enum Double where
succ :: Double -> Double
succ Double
x = Double
x Double -> Double -> Double
forall a. Num a => a -> a -> a
+ Double
1
pred :: Double -> Double
pred Double
x = Double
x Double -> Double -> Double
forall a. Num a => a -> a -> a
- Double
1
toEnum :: Int -> Double
toEnum = Int -> Double
int2Double
fromEnum :: Double -> Int
fromEnum = Integer -> Int
forall a. Num a => Integer -> a
fromInteger (Integer -> Int) -> (Double -> Integer) -> Double -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Integer
forall a b. (RealFrac a, Integral b) => a -> b
truncate
enumFrom :: Double -> [Double]
enumFrom = Double -> [Double]
forall a. Fractional a => a -> [a]
numericEnumFrom
enumFromTo :: Double -> Double -> [Double]
enumFromTo = Double -> Double -> [Double]
forall a. (Ord a, Fractional a) => a -> a -> [a]
numericEnumFromTo
enumFromThen :: Double -> Double -> [Double]
enumFromThen = Double -> Double -> [Double]
forall a. Fractional a => a -> a -> [a]
numericEnumFromThen
enumFromThenTo :: Double -> Double -> Double -> [Double]
enumFromThenTo = Double -> Double -> Double -> [Double]
forall a. (Ord a, Fractional a) => a -> a -> a -> [a]
numericEnumFromThenTo
showFloat :: (RealFloat a) => a -> ShowS showFloat :: forall a. RealFloat a => a -> ShowS showFloat a x = String -> ShowS showString (FFFormat -> Maybe Int -> a -> String forall a. RealFloat a => FFFormat -> Maybe Int -> a -> String formatRealFloat FFFormat FFGeneric Maybe Int forall a. Maybe a Nothing a x)
data FFFormat = FFExponent | FFFixed | FFGeneric
formatRealFloat :: (RealFloat a) => FFFormat -> Maybe Int -> a -> String formatRealFloat :: forall a. RealFloat a => FFFormat -> Maybe Int -> a -> String formatRealFloat FFFormat fmt Maybe Int decs a x = FFFormat -> Maybe Int -> Bool -> a -> String forall a. RealFloat a => FFFormat -> Maybe Int -> Bool -> a -> String formatRealFloatAlt FFFormat fmt Maybe Int decs Bool False a x
formatRealFloatAlt :: (RealFloat a) => FFFormat -> Maybe Int -> Bool -> a -> String formatRealFloatAlt :: forall a. RealFloat a => FFFormat -> Maybe Int -> Bool -> a -> String formatRealFloatAlt FFFormat fmt Maybe Int decs Bool alt a x | a -> Bool forall a. RealFloat a => a -> Bool isNaN a x = String "NaN" | a -> Bool forall a. RealFloat a => a -> Bool isInfinite a x = if a x a -> a -> Bool forall a. Ord a => a -> a -> Bool < a 0 then String "-Infinity" else String "Infinity" | a x a -> a -> Bool forall a. Ord a => a -> a -> Bool < a 0 Bool -> Bool -> Bool || a -> Bool forall a. RealFloat a => a -> Bool isNegativeZero a x = Char '-'Char -> ShowS forall a. a -> [a] -> [a] :FFFormat -> ([Int], Int) -> String doFmt FFFormat fmt (Integer -> a -> ([Int], Int) forall a. RealFloat a => Integer -> a -> ([Int], Int) floatToDigits (Int -> Integer forall a. Integral a => a -> Integer toInteger Int base) (-a x)) | Bool otherwise = FFFormat -> ([Int], Int) -> String doFmt FFFormat fmt (Integer -> a -> ([Int], Int) forall a. RealFloat a => Integer -> a -> ([Int], Int) floatToDigits (Int -> Integer forall a. Integral a => a -> Integer toInteger Int base) a x) where base :: Int base = Int 10
doFmt :: FFFormat -> ([Int], Int) -> String doFmt FFFormat format ([Int] is, Int e) = let ds :: String ds = (Int -> Char) -> [Int] -> String forall a b. (a -> b) -> [a] -> [b] map Int -> Char intToDigit [Int] is in case FFFormat format of FFFormat FFGeneric -> FFFormat -> ([Int], Int) -> String doFmt (if Int e Int -> Int -> Bool forall a. Ord a => a -> a -> Bool < Int 0 Bool -> Bool -> Bool || Int e Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > Int 7 then FFFormat FFExponent else FFFormat FFFixed) ([Int] is,Int e) FFFormat FFExponent -> case Maybe Int decs of Maybe Int Nothing -> let show_e' :: String show_e' = Int -> String forall a. Show a => a -> String show (Int eInt -> Int -> Int forall a. Num a => a -> a -> a -Int
- in case String
ds of String "0" -> String "0.0e0" [Char d] -> Char d Char -> ShowS forall a. a -> [a] -> [a] : String ".0e" String -> ShowS forall a. [a] -> [a] -> [a] ++ String show_e' (Char d:String ds') -> Char d Char -> ShowS forall a. a -> [a] -> [a] : Char '.' Char -> ShowS forall a. a -> [a] -> [a] : String ds' String -> ShowS forall a. [a] -> [a] -> [a] ++ String "e" String -> ShowS forall a. [a] -> [a] -> [a] ++ String show_e' [] -> ShowS forall a. String -> a errorWithoutStackTrace String "formatRealFloat/doFmt/FFExponent: []" Just Int d | Int d Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <= Int 0 ->
case [Int]is of [Int 0] -> String "0e0" [Int] _ -> let (Int ei,[Int] is') = Int -> Int -> [Int] -> (Int, [Int]) roundTo Int base Int 1 [Int] is Char n:String _ = (Int -> Char) -> [Int] -> String forall a b. (a -> b) -> [a] -> [b] map Int -> Char intToDigit (if Int ei Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > Int 0 then [Int] -> [Int] forall a. [a] -> [a] init [Int] is' else [Int] is') in Char n Char -> ShowS forall a. a -> [a] -> [a] : Char 'e' Char -> ShowS forall a. a -> [a] -> [a] : Int -> String forall a. Show a => a -> String show (Int eInt -> Int -> Int forall a. Num a => a -> a -> a -Int 1Int -> Int -> Int forall a. Num a => a -> a -> a +Int ei) Just Int dec -> let dec' :: Int dec' = Int -> Int -> Int forall a. Ord a => a -> a -> a max Int dec Int 1 in case [Int] is of [Int 0] -> Char '0' Char -> ShowS forall a. a -> [a] -> [a] :Char '.' Char -> ShowS forall a. a -> [a] -> [a] : Int -> ShowS forall a. Int -> [a] -> [a] take Int dec' (Char -> String forall a. a -> [a] repeat Char '0') String -> ShowS forall a. [a] -> [a] -> [a] ++ String "e0" [Int] _ -> let (Int ei,[Int] is') = Int -> Int -> [Int] -> (Int, [Int]) roundTo Int base (Int dec'Int -> Int -> Int forall a. Num a => a -> a -> a +Int
- [Int] is (Char
d:String ds') = (Int -> Char) -> [Int] -> String forall a b. (a -> b) -> [a] -> [b] map Int -> Char intToDigit (if Int ei Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > Int 0 then [Int] -> [Int] forall a. [a] -> [a] init [Int] is' else [Int] is') in Char dChar -> ShowS forall a. a -> [a] -> [a] :Char '.'Char -> ShowS forall a. a -> [a] -> [a] :String ds' String -> ShowS forall a. [a] -> [a] -> [a] ++ Char 'e'Char -> ShowS forall a. a -> [a] -> [a] :Int -> String forall a. Show a => a -> String show (Int eInt -> Int -> Int forall a. Num a => a -> a -> a -Int 1Int -> Int -> Int forall a. Num a => a -> a -> a +Int ei) FFFormat FFFixed -> let mk0 :: ShowS mk0 String ls = case String ls of { String "" -> String "0" ; String _ -> String ls} in case Maybe Int decs of Maybe Int Nothing | Int e Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <= Int 0 -> String "0." String -> ShowS forall a. [a] -> [a] -> [a] ++ Int -> Char -> String forall a. Int -> a -> [a] replicate (-Int e) Char '0' String -> ShowS forall a. [a] -> [a] -> [a] ++ String ds | Bool otherwise -> let f :: t -> String -> ShowS f t 0 String s String rs = ShowS mk0 (ShowS forall a. [a] -> [a] reverse String s) String -> ShowS forall a. [a] -> [a] -> [a] ++ Char '.'Char -> ShowS forall a. a -> [a] -> [a] :ShowS mk0 String rs f t n String s String "" = t -> String -> ShowS f (t nt -> t -> t forall a. Num a => a -> a -> a -t
n String s (Char r:String rs) = t -> String -> ShowS f (t nt -> t -> t forall a. Num a => a -> a -> a -t
forall {t}. (Eq t, Num t) => t -> String -> ShowS f Int e String "" String ds Just Int dec -> let dec' :: Int dec' = Int -> Int -> Int forall a. Ord a => a -> a -> a max Int dec Int 0 in if Int e Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >= Int 0 then let (Int ei,[Int] is') = Int -> Int -> [Int] -> (Int, [Int]) roundTo Int base (Int dec' Int -> Int -> Int forall a. Num a => a -> a -> a + Int e) [Int] is (String ls,String rs) = Int -> String -> (String, String) forall a. Int -> [a] -> ([a], [a]) splitAt (Int eInt -> Int -> Int forall a. Num a => a -> a -> a +Int ei) ((Int -> Char) -> [Int] -> String forall a b. (a -> b) -> [a] -> [b] map Int -> Char intToDigit [Int] is') in ShowS mk0 String ls String -> ShowS forall a. [a] -> [a] -> [a] ++ (if String -> Bool forall a. [a] -> Bool null String rs Bool -> Bool -> Bool && Bool -> Bool not Bool alt then String "" else Char '.'Char -> ShowS forall a. a -> [a] -> [a] :String rs) else let (Int ei,[Int] is') = Int -> Int -> [Int] -> (Int, [Int]) roundTo Int base Int dec' (Int -> Int -> [Int] forall a. Int -> a -> [a] replicate (-Int e) Int 0 [Int] -> [Int] -> [Int] forall a. [a] -> [a] -> [a] ++ [Int] is) Char d:String ds' = (Int -> Char) -> [Int] -> String forall a b. (a -> b) -> [a] -> [b] map Int -> Char intToDigit (if Int ei Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > Int 0 then [Int] is' else Int 0Int -> [Int] -> [Int] forall a. a -> [a] -> [a] :[Int] is') in Char d Char -> ShowS forall a. a -> [a] -> [a] : (if String -> Bool forall a. [a] -> Bool null String ds' Bool -> Bool -> Bool && Bool -> Bool not Bool alt then String "" else Char '.'Char -> ShowS forall a. a -> [a] -> [a] :String ds')
roundTo :: Int -> Int -> [Int] -> (Int,[Int])
roundTo :: Int -> Int -> [Int] -> (Int, [Int])
roundTo Int
base Int
d [Int]
is =
case Int -> Bool -> [Int] -> (Int, [Int])
f Int
d Bool
True [Int]
is of
x :: (Int, [Int])
x@(Int
0,[Int]
_) -> (Int, [Int])
x
(Int
1,[Int]
xs) -> (Int
1, Int
1Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
xs)
(Int, [Int])
_ -> String -> (Int, [Int])
forall a. String -> a
errorWithoutStackTrace String
"roundTo: bad Value"
where
b2 :: Int
b2 = Int
base Int -> Int -> Int
forall a. Integral a => a -> a -> a
quot Int
2
f :: Int -> Bool -> [Int] -> (Int, [Int])
f Int
n Bool
_ [] = (Int
0, Int -> Int -> [Int]
forall a. Int -> a -> [a]
replicate Int
n Int
0)
f Int
0 Bool
e (Int
x:[Int]
xs) | Int
x Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
b2 Bool -> Bool -> Bool
&& Bool
e Bool -> Bool -> Bool
&& (Int -> Bool) -> [Int] -> Bool
forall a. (a -> Bool) -> [a] -> Bool
all (Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0) [Int]
xs = (Int
0, [])
| Bool
otherwise = (if Int
x Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
b2 then Int
1 else Int
0, [])
f Int
n Bool
_ (Int
i:[Int]
xs)
| Int
i' Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
base = (Int
1,Int
0Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
ds)
| Bool
otherwise = (Int
0,Int
i'Int -> [Int] -> [Int]
forall a. a -> [a] -> [a]
:[Int]
ds)
where
(Int
c,[Int]
ds) = Int -> Bool -> [Int] -> (Int, [Int])
f (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
i' = Int c Int -> Int -> Int forall a. Num a => a -> a -> a + Int i
floatToDigits :: (RealFloat a) => Integer -> a -> ([Int], Int) floatToDigits :: forall a. RealFloat a => Integer -> a -> ([Int], Int) floatToDigits Integer _ a 0 = ([Int 0], Int 0) floatToDigits Integer base a x = let (Integer f0, Int e0) = a -> (Integer, Int) forall a. RealFloat a => a -> (Integer, Int) decodeFloat a x (Int minExp0, Int _) = a -> (Int, Int) forall a. RealFloat a => a -> (Int, Int) floatRange a x p :: Int p = a -> Int forall a. RealFloat a => a -> Int floatDigits a x b :: Integer b = a -> Integer forall a. RealFloat a => a -> Integer floatRadix a x minExp :: Int minExp = Int minExp0 Int -> Int -> Int forall a. Num a => a -> a -> a - Int p
(Integer
f, Int
e) =
let n :: Int
n = Int
minExp Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
e0 in
if Int
n Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0 then (Integer
f0 Integer -> Integer -> Integer
forall a. Integral a => a -> a -> a
quot (Integer -> Int -> Integer
expt Integer
b Int
n), Int
e0Int -> Int -> Int
forall a. Num a => a -> a -> a
+Int
n) else (Integer
f0, Int
e0)
(Integer
r, Integer
s, Integer
mUp, Integer
mDn) =
if Int
e Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 then
let be :: Integer
be = Integer -> Int -> Integer
expt Integer
b Int
e in
if Integer
f Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer -> Int -> Integer
expt Integer
b (Int
pInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
- then
(Integer
fInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
beInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
bInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
2, Integer
2Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
b, Integer
beInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
*Integer
b, Integer
be)
else (Integer fInteger -> Integer -> Integer forall a. Num a => a -> a -> a *Integer beInteger -> Integer -> Integer forall a. Num a => a -> a -> a *Integer 2, Integer 2, Integer be, Integer be) else if Int e Int -> Int -> Bool forall a. Ord a => a -> a -> Bool > Int minExp Bool -> Bool -> Bool && Integer f Integer -> Integer -> Bool forall a. Eq a => a -> a -> Bool == Integer -> Int -> Integer expt Integer b (Int pInt -> Int -> Int forall a. Num a => a -> a -> a -Int - then (Integer fInteger -> Integer -> Integer forall a. Num a => a -> a -> a *Integer bInteger -> Integer -> Integer forall a. Num a => a -> a -> a *Integer 2, Integer -> Int -> Integer expt Integer b (-Int eInt -> Int -> Int forall a. Num a => a -> a -> a +Int 1)Integer -> Integer -> Integer forall a. Num a => a -> a -> a *Integer 2, Integer b, Integer
- else (Integer
fInteger -> Integer -> Integer forall a. Num a => a -> a -> a *Integer 2, Integer -> Int -> Integer expt Integer b (-Int e)Integer -> Integer -> Integer forall a. Num a => a -> a -> a *Integer 2, Integer 1, Integer 1) k :: Int k :: Int k = let k0 :: Int k0 :: Int k0 = if Integer b Integer -> Integer -> Bool forall a. Eq a => a -> a -> Bool == Integer 2 Bool -> Bool -> Bool && Integer base Integer -> Integer -> Bool forall a. Eq a => a -> a -> Bool == Integer 10 then
let lx :: Intlx = Int
p Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
e0
k1 :: Int
k1 = (Int
lx Int -> Int -> Int
forall a. Num a => a -> a -> a
* Int
8651) Int -> Int -> Int
forall a. Integral a => a -> a -> a
quot Int
28738
in if Int
lx Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
>= Int
0 then Int
k1 Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1 else Int
k1
else
Float -> Intforall a b. (RealFrac a, Integral b) => a -> b ceiling ((Float -> Float forall a. Floating a => a -> a log (Integer -> Float forall a. Num a => Integer -> a fromInteger (Integer fInteger -> Integer -> Integer forall a. Num a => a -> a -> a +Integer
forall a b. (Integral a, Num b) => a -> b fromIntegral Int e Float -> Float -> Float forall a. Num a => a -> a -> a * Float -> Float forall a. Floating a => a -> a log (Integer -> Float forall a. Num a => Integer -> a fromInteger Integer b)) Float -> Float -> Float forall a. Fractional a => a -> a -> a / Float -> Float forall a. Floating a => a -> a log (Integer -> Float forall a. Num a => Integer -> a fromInteger Integer base))
fixup :: Int -> Intfixup Int n = if Int n Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >= Int 0 then if Integer r Integer -> Integer -> Integer forall a. Num a => a -> a -> a + Integer mUp Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool <= Integer -> Int -> Integer expt Integer base Int n Integer -> Integer -> Integer forall a. Num a => a -> a -> a * Integer s then Int n else Int -> Int fixup (Int nInt -> Int -> Int forall a. Num a => a -> a -> a +Int 1) else if Integer -> Int -> Integer expt Integer base (-Int n) Integer -> Integer -> Integer forall a. Num a => a -> a -> a * (Integer r Integer -> Integer -> Integer forall a. Num a => a -> a -> a + Integer mUp) Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool <= Integer s then Int n else Int -> Int fixup (Int nInt -> Int -> Int forall a. Num a => a -> a -> a +Int 1) in Int -> Int fixup Int k0
gen :: [Integer] -> Integer -> Integer -> Integer -> Integer -> [Integer]
gen [Integer]
ds Integer
rn Integer
sN Integer
mUpN Integer
mDnN =
let
(Integer
dn, Integer
rn') = (Integer
rn Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
base) Integer -> Integer -> (Integer, Integer)
forall a. Integral a => a -> a -> (a, a)
quotRem Integer
sN
mUpN' :: Integer
mUpN' = Integer
mUpN Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
base
mDnN' :: Integer
mDnN' = Integer
mDnN Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
base
in
case (Integer
rn' Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
mDnN', Integer
rn' Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
mUpN' Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
sN) of
(Bool
True, Bool
False) -> Integer
dn Integer -> [Integer] -> [Integer]
forall a. a -> [a] -> [a]
: [Integer]
ds
(Bool
False, Bool
True) -> Integer
dnInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
1 Integer -> [Integer] -> [Integer]
forall a. a -> [a] -> [a]
: [Integer]
ds
(Bool
True, Bool
True) -> if Integer
rn' Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
* Integer
2 Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
sN then Integer
dn Integer -> [Integer] -> [Integer]
forall a. a -> [a] -> [a]
: [Integer]
ds else Integer
dnInteger -> Integer -> Integer
forall a. Num a => a -> a -> a
+Integer
1 Integer -> [Integer] -> [Integer]
forall a. a -> [a] -> [a]
: [Integer]
ds
(Bool
False, Bool
False) -> [Integer] -> Integer -> Integer -> Integer -> Integer -> [Integer]
gen (Integer
dnInteger -> [Integer] -> [Integer]
forall a. a -> [a] -> [a]
:[Integer]
ds) Integer
rn' Integer
sN Integer
mUpN' Integer
mDnN'
rds :: [Integer] rds = if Int k Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >= Int 0 then [Integer] -> Integer -> Integer -> Integer -> Integer -> [Integer] gen [] Integer r (Integer s Integer -> Integer -> Integer forall a. Num a => a -> a -> a * Integer -> Int -> Integer expt Integer base Int k) Integer mUp Integer mDn else let bk :: Integer bk = Integer -> Int -> Integer expt Integer base (-Int k) in [Integer] -> Integer -> Integer -> Integer -> Integer -> [Integer] gen [] (Integer r Integer -> Integer -> Integer forall a. Num a => a -> a -> a * Integer bk) Integer s (Integer mUp Integer -> Integer -> Integer forall a. Num a => a -> a -> a * Integer bk) (Integer mDn Integer -> Integer -> Integer forall a. Num a => a -> a -> a * Integer bk) in ((Integer -> Int) -> [Integer] -> [Int] forall a b. (a -> b) -> [a] -> [b] map Integer -> Int forall a b. (Integral a, Num b) => a -> b fromIntegral ([Integer] -> [Integer] forall a. [a] -> [a] reverse [Integer] rds), Int k)
{-# SPECIALISE integerToBinaryFloat' :: Integer -> Float, Integer -> Double #-}
integerToBinaryFloat' :: RealFloat a => Integer -> a
integerToBinaryFloat' :: forall a. RealFloat a => Integer -> a
integerToBinaryFloat' Integer
n = a
result
where
mantDigs :: Int
mantDigs = a -> Int
forall a. RealFloat a => a -> Int
floatDigits a
result
k :: Int
k = Int# -> Int
I# (Word# -> Int#
word2Int# (Integer -> Word#
integerLog2# Integer
n))
result :: a
result = if Int
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
mantDigs then
Integer -> Int -> a
forall a. RealFloat a => Integer -> Int -> a
encodeFloat Integer
n Int
0
else
let !e :: Int
e@(I# Int#
e#) = Int
k Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
mantDigs Int -> Int -> Int
forall a. Num a => a -> a -> a
+ Int
1
q :: Integer
q = Integer
n Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
unsafeShiftR Int
e
n' :: Integer
n' = case Integer -> Int# -> Int#
roundingMode# Integer
n (Int#
e# Int# -> Int# -> Int#
-# Int#
1#) of
Int#
0# -> Integer
q
Int#
1# -> if Integer -> Int
integerToInt Integer
q Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. Int
1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0 then
Integer
q
else
Integer
q Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
1
Int#
_ -> Integer
q Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
1
in Integer -> Int -> a
forall a. RealFloat a => Integer -> Int -> a
encodeFloat Integer
n' Int
e
{-# RULES "fromRat/Float" fromRat = (fromRational :: Rational -> Float) "fromRat/Double" fromRat = (fromRational :: Rational -> Double) #-}
{-# NOINLINE [1] fromRat #-} fromRat :: (RealFloat a) => Rational -> a
fromRat :: forall a. RealFloat a => Rational -> a
fromRat (Integer
n :% Integer
0) | Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
> Integer
0 = a
1a -> a -> a
forall a. Fractional a => a -> a -> a
/a
0
| Integer
n Integer -> Integer -> Bool
forall a. Ord a => a -> a -> Bool
< Integer
0 = -a
1a -> a -> a
forall a. Fractional a => a -> a -> a
/a
0
| Bool
otherwise = a
0a -> a -> a
forall a. Fractional a => a -> a -> a
/a
0
fromRat (Integer n :% Integer d) | Integer n Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool > Integer 0 = Rational -> a forall a. RealFloat a => Rational -> a fromRat' (Integer n Integer -> Integer -> Rational forall a. a -> a -> Ratio a :% Integer d) | Integer n Integer -> Integer -> Bool forall a. Ord a => a -> a -> Bool < Integer 0 = - Rational -> a forall a. RealFloat a => Rational -> a fromRat' ((-Integer n) Integer -> Integer -> Rational forall a. a -> a -> Ratio a :% Integer d) | Bool otherwise = Integer -> Int -> a forall a. RealFloat a => Integer -> Int -> a encodeFloat Integer 0 Int 0
fromRat' :: (RealFloat a) => Rational -> a
fromRat' :: forall a. RealFloat a => Rational -> a
fromRat' Rational
x = a
r
where b :: Integer
b = a -> Integer
forall a. RealFloat a => a -> Integer
floatRadix a
r
p :: Int
p = a -> Int
forall a. RealFloat a => a -> Int
floatDigits a
r
(Int
minExp0, Int
_) = a -> (Int, Int)
forall a. RealFloat a => a -> (Int, Int)
floatRange a
r
minExp :: Int
minExp = Int
minExp0 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
p
xMax :: Rational
xMax = Integer -> Rational
forall a. Real a => a -> Rational
toRational (Integer -> Int -> Integer
expt Integer
b Int
p)
ln :: Int
ln = Int# -> Int
I# (Word# -> Int#
word2Int# (Integer -> Integer -> Word#
integerLogBase# Integer
b (Rational -> Integer
forall a. Ratio a -> a
numerator Rational
x)))
ld :: Int
ld = Int# -> Int
I# (Word# -> Int#
word2Int# (Integer -> Integer -> Word#
integerLogBase# Integer
b (Rational -> Integer
forall a. Ratio a -> a
denominator Rational
x)))
p0 :: Int
p0 = (Int
ln Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
ld Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
p) Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
minExp
f :: Rationalf = if Int p0 Int -> Int -> Bool forall a. Ord a => a -> a -> Bool < Int 0 then Integer 1 Integer -> Integer -> Rational forall a. a -> a -> Ratio a :% Integer -> Int -> Integer expt Integer b (-Int p0) else Integer -> Int -> Integer expt Integer b Int p0 Integer -> Integer -> Rational forall a. a -> a -> Ratio a :% Integer 1 x0 :: Rational x0 = Rational x Rational -> Rational -> Rational forall a. Fractional a => a -> a -> a / Rational f
(Rationalx', Int p') = if Rational x0 Rational -> Rational -> Bool forall a. Ord a => a -> a -> Bool >= Rational xMax then (Rational x0 Rational -> Rational -> Rational forall a. Fractional a => a -> a -> a / Integer -> Rational forall a. Real a => a -> Rational toRational Integer b, Int p0Int -> Int -> Int forall a. Num a => a -> a -> a +Int
r = Integer -> Int -> a forall a. RealFloat a => Integer -> Int -> a encodeFloat (Rational -> Integer forall a b. (RealFrac a, Integral b) => a -> b round Rational x') Int p'
minExpt, maxExpt :: Int minExpt :: Int minExpt = Int 0 maxExpt :: Int maxExpt = Int 1100
expt :: Integer -> Int -> Integer expt :: Integer -> Int -> Integer expt Integer base Int n = if Integer base Integer -> Integer -> Bool forall a. Eq a => a -> a -> Bool == Integer 2 Bool -> Bool -> Bool && Int n Int -> Int -> Bool forall a. Ord a => a -> a -> Bool >= Int minExpt Bool -> Bool -> Bool && Int n Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <= Int maxExpt then Array Int Integer exptsArray Int Integer -> Int -> Integer forall i e. Ix i => Array i e -> i -> e !Int n else if Integer base Integer -> Integer -> Bool forall a. Eq a => a -> a -> Bool == Integer 10 Bool -> Bool -> Bool && Int n Int -> Int -> Bool forall a. Ord a => a -> a -> Bool <= Int maxExpt10 then Array Int Integer expts10Array Int Integer -> Int -> Integer forall i e. Ix i => Array i e -> i -> e !Int n else Integer baseInteger -> Int -> Integer forall a b. (Num a, Integral b) => a -> b -> a ^Int n
expts :: Array Int Integer expts :: Array Int Integer expts = (Int, Int) -> [(Int, Integer)] -> Array Int Integer forall i e. Ix i => (i, i) -> [(i, e)] -> Array i e array (Int minExpt,Int maxExpt) [(Int n,Integer 2Integer -> Int -> Integer forall a b. (Num a, Integral b) => a -> b -> a ^Int n) | Int n <- [Int minExpt .. Int maxExpt]]
maxExpt10 :: Int maxExpt10 :: Int maxExpt10 = Int 324
expts10 :: Array Int Integer expts10 :: Array Int Integer expts10 = (Int, Int) -> [(Int, Integer)] -> Array Int Integer forall i e. Ix i => (i, i) -> [(i, e)] -> Array i e array (Int minExpt,Int maxExpt10) [(Int n,Integer 10Integer -> Int -> Integer forall a b. (Num a, Integral b) => a -> b -> a ^Int n) | Int n <- [Int minExpt .. Int maxExpt10]]
{-# SPECIALISE fromRat'' :: Int -> Int -> Integer -> Integer -> Float, Int -> Int -> Integer -> Integer -> Double #-} fromRat'' :: RealFloat a => Int -> Int -> Integer -> Integer -> a
fromRat'' :: forall a. RealFloat a => Int -> Int -> Integer -> Integer -> a fromRat'' minEx :: Int minEx@(I# Int# me#) mantDigs :: Int mantDigs@(I# Int# md#) Integer n Integer d = case Integer -> (# (# #) | Word# #) integerIsPowerOf2# Integer d of (# | Word# ldw# #) -> let ld# :: Int# ld# = Word# -> Int# word2Int# Word# ldw# in case Word# -> Int# word2Int# (Integer -> Word# integerLog2# Integer n) of Int# ln# | Int# -> Bool isTrue# (Int# ln# Int# -> Int# -> Int# >=# (Int# ld# Int# -> Int# -> Int# +# Int# me# Int# -> Int# -> Int# -# Int# 1#)) ->
if Int# -> BoolisTrue# (Int#
ln# Int# -> Int# -> Int#
<# Int#
md#)
then Integer -> Int -> a
forall a. RealFloat a => Integer -> Int -> a
encodeFloat Integer
n (Int# -> Int
I# (Int# -> Int#
negateInt# Int#
ld#))
else let n' :: Integer
n' = Integer
n Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftR (Int# -> Int
I# (Int#
ln# Int# -> Int# -> Int#
+# Int#
1# Int# -> Int# -> Int#
-# Int#
md#))
n'' :: Integer
n'' = case Integer -> Int# -> Int#
roundingMode# Integer
n (Int#
ln# Int# -> Int# -> Int#
-# Int#
md#) of
Int#
0# -> Integer
n'
Int#
2# -> Integer
n' Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
1
Int#
_ -> case Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
n' Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. (Int
1 :: Int) of
Int
0 -> Integer
n'
Int
_ -> Integer
n' Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
1
in Integer -> Int -> a
forall a. RealFloat a => Integer -> Int -> a
encodeFloat Integer
n'' (Int# -> Int
I# (Int#
ln# Int# -> Int# -> Int#
-# Int#
ld# Int# -> Int# -> Int#
+# Int#
1# Int# -> Int# -> Int#
-# Int#
md#))
| Bool
otherwise ->
case Int#ld# Int# -> Int# -> Int#
+# (Int#
me# Int# -> Int# -> Int#
-# Int#
md#) of
Int#
ld'# | Int# -> Bool
isTrue# (Int#
ld'# Int# -> Int# -> Int#
<=# Int#
0#) ->
Integer -> Int -> a
forall a. RealFloat a => Integer -> Int -> a
encodeFloat Integer
n (Int# -> Int
I# ((Int#
me# Int# -> Int# -> Int#
-# Int#
md#) Int# -> Int# -> Int#
-# Int#
ld'#))
| Int# -> Bool
isTrue# (Int#
ld'# Int# -> Int# -> Int#
<=# Int#
ln#) ->
let n' :: Integer
n' = Integer
n Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftR (Int# -> Int
I# Int#
ld'#)
in case Integer -> Int# -> Int#
roundingMode# Integer
n (Int#
ld'# Int# -> Int# -> Int#
-# Int#
1#) of
Int#
0# -> Integer -> Int -> a
forall a. RealFloat a => Integer -> Int -> a
encodeFloat Integer
n' (Int
minEx Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
mantDigs)
Int#
1# -> if Integer -> Int
forall a. Num a => Integer -> a
fromInteger Integer
n' Int -> Int -> Int
forall a. Bits a => a -> a -> a
.&. (Int
1 :: Int) Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
0
then Integer -> Int -> a
forall a. RealFloat a => Integer -> Int -> a
encodeFloat Integer
n' (Int
minExInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
mantDigs)
else Integer -> Int -> a
forall a. RealFloat a => Integer -> Int -> a
encodeFloat (Integer
n' Integer -> Integer -> Integer
forall a. Num a => a -> a -> a
+ Integer
_ -> Integer -> Int -> a forall a. RealFloat a => Integer -> Int -> a encodeFloat (Integer n' Integer -> Integer -> Integer forall a. Num a => a -> a -> a + Integer
isTrue# (Int#
ld'# Int# -> Int# -> Int#
># (Int#
ln# Int# -> Int# -> Int#
+# Int#
1#)) -> Integer -> Int -> a
forall a. RealFloat a => Integer -> Int -> a
encodeFloat Integer
0 Int
0
| Bool
otherwise ->
case Integer -> (# (# #) | Word# #)
integerIsPowerOf2# Integer
n of
(# | Word#
_ #) -> Integer -> Int -> a
forall a. RealFloat a => Integer -> Int -> a
encodeFloat Integer
0 Int
0
(# (# #) | #) -> Integer -> Int -> a
forall a. RealFloat a => Integer -> Int -> a
encodeFloat Integer
1 (Int
minEx Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
mantDigs)
(# (# #) | #) ->
let ln :: Int
ln = Int# -> Int
I# (Word# -> Int#
word2Int# (Integer -> Word#
integerLog2# Integer
n))
ld :: Int
ld = Int# -> Int
I# (Word# -> Int#
word2Int# (Integer -> Word#
integerLog2# Integer
d))
p0 :: Intp0 = Int -> Int -> Int
forall a. Ord a => a -> a -> a
max Int
minEx (Int
ln Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
ld)
(Integer
n', Integer
d')
| Int
p0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
mantDigs = (Integer
n Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL (Int
mantDigs Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
p0), Integer
d)
| Int
p0 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
mantDigs = (Integer
n, Integer
d)
| Bool
otherwise = (Integer
n, Integer
d Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL (Int
p0 Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
mantDigs))
scale :: a -> c -> c -> (a, c, c)scale a
p c
a c
b
| (c
b c -> Int -> c
forall a. Bits a => a -> Int -> a
shiftL Int
mantDigs) c -> c -> Bool
forall a. Ord a => a -> a -> Bool
<= c
a = (a
pa -> a -> a
forall a. Num a => a -> a -> a
+a
1, c
a, c
b c -> Int -> c
forall a. Bits a => a -> Int -> a
shiftL Int
1)
| Bool
otherwise = (a
p, c
a, c
b)
(Int
p', Integer
n'', Integer
d'') = Int -> Integer -> Integer -> (Int, Integer, Integer)
forall {c} {a}. (Ord c, Bits c, Num a) => a -> c -> c -> (a, c, c)
scale (Int
p0Int -> Int -> Int
forall a. Num a => a -> a -> a
-Int
mantDigs) Integer
n' Integer
d'
rdq :: Integerrdq = case Integer
n'' Integer -> Integer -> (Integer, Integer)
forall a. Integral a => a -> a -> (a, a)
quotRem Integer
d'' of
(Integer
q,Integer
r) -> case Integer -> Integer -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (Integer
r Integer -> Int -> Integer
forall a. Bits a => a -> Int -> a
shiftL Int
- Integer d'' of Ordering
LT -> Integer q Ordering EQ -> if Integer -> Int forall a. Num a => Integer -> a fromInteger Integer q Int -> Int -> Int forall a. Bits a => a -> a -> a .&. (Int 1 :: Int) Int -> Int -> Bool forall a. Eq a => a -> a -> Bool == Int 0 then Integer q else Integer qInteger -> Integer -> Integer forall a. Num a => a -> a -> a +Integer 1 Ordering GT -> Integer qInteger -> Integer -> Integer forall a. Num a => a -> a -> a +Integer 1 in Integer -> Int -> a forall a. RealFloat a => Integer -> Int -> a encodeFloat Integer rdq Int p'
roundingMode# :: Integer -> Int# -> Int#
roundingMode# :: Integer -> Int# -> Int#
roundingMode# (IS Int#
i#) Int#
t =
let
k :: Word#
k = Int# -> Word#
int2Word# Int#
i# Word# -> Word# -> Word#
and# ((Word# -> Int# -> Word#
uncheckedShiftL# Word#
2## Int#
t) Word# -> Word# -> Word#
minusWord# Word#
1##)
c :: Word#
c = Word# -> Int# -> Word#
uncheckedShiftL# Word#
1## Int#
t
in if Int# -> Bool
isTrue# (Word#
c Word# -> Word# -> Int#
gtWord# Word#
k)
then Int#
0#
else if Int# -> Bool
isTrue# (Word#
c Word# -> Word# -> Int#
ltWord# Word#
k)
then Int#
2#
else Int#
1#
roundingMode# (IN ByteArray#
bn) Int#
t = Integer -> Int# -> Int#
roundingMode# (ByteArray# -> Integer
IP ByteArray#
bn) Int#
t
roundingMode# (IP ByteArray#
bn) Int#
t =
let
j :: Int#
j = Word# -> Int#
word2Int# (Int# -> Word#
int2Word# Int#
t Word# -> Word# -> Word#
and# MMASK##)
k :: Int#
k = Int# -> Int# -> Int#
uncheckedIShiftRA# Int#
t WSHIFT#
r :: Word#
r = ByteArray# -> Int# -> Word#
bigNatIndex# ByteArray#
bn Int#
k Word# -> Word# -> Word#
and# ((Word# -> Int# -> Word#
uncheckedShiftL# Word#
2## Int#
j) Word# -> Word# -> Word#
minusWord# Word#
1##)
c :: Word#
c = Word# -> Int# -> Word#
uncheckedShiftL# Word#
1## Int#
j
test :: Int# -> Int#
test Int#
i = if Int# -> Bool
isTrue# (Int#
i Int# -> Int# -> Int#
<# Int#
0#)
then Int#
1#
else case ByteArray# -> Int# -> Word#
bigNatIndex# ByteArray#
bn Int#
i of
Word#
0## -> Int# -> Int#
test (Int#
i Int# -> Int# -> Int#
-# Int#
1#)
Word#
_ -> Int#
2#
in if Int# -> Bool
isTrue# (Word#
c Word# -> Word# -> Int#
gtWord# Word#
r)
then Int#
0#
else if Int# -> Bool
isTrue# (Word#
c Word# -> Word# -> Int#
ltWord# Word#
r)
then Int#
2#
else Int# -> Int#
test (Int#
k Int# -> Int# -> Int#
-# Int#
1#)
plusFloat, minusFloat, timesFloat, divideFloat :: Float -> Float -> Float plusFloat :: Float -> Float -> Float plusFloat (F# Float# x) (F# Float# y) = Float# -> Float F# (Float# -> Float# -> Float# plusFloat# Float# x Float# y) minusFloat :: Float -> Float -> Float minusFloat (F# Float# x) (F# Float# y) = Float# -> Float F# (Float# -> Float# -> Float# minusFloat# Float# x Float# y) timesFloat :: Float -> Float -> Float timesFloat (F# Float# x) (F# Float# y) = Float# -> Float F# (Float# -> Float# -> Float# timesFloat# Float# x Float# y) divideFloat :: Float -> Float -> Float divideFloat (F# Float# x) (F# Float# y) = Float# -> Float F# (Float# -> Float# -> Float# divideFloat# Float# x Float# y)
negateFloat :: Float -> Float negateFloat :: Float -> Float negateFloat (F# Float# x) = Float# -> Float F# (Float# -> Float# negateFloat# Float# x)
gtFloat, geFloat, ltFloat, leFloat :: Float -> Float -> Bool gtFloat :: Float -> Float -> Bool gtFloat (F# Float# x) (F# Float# y) = Int# -> Bool isTrue# (Float# -> Float# -> Int# gtFloat# Float# x Float# y) geFloat :: Float -> Float -> Bool geFloat (F# Float# x) (F# Float# y) = Int# -> Bool isTrue# (Float# -> Float# -> Int# geFloat# Float# x Float# y) ltFloat :: Float -> Float -> Bool ltFloat (F# Float# x) (F# Float# y) = Int# -> Bool isTrue# (Float# -> Float# -> Int# ltFloat# Float# x Float# y) leFloat :: Float -> Float -> Bool leFloat (F# Float# x) (F# Float# y) = Int# -> Bool isTrue# (Float# -> Float# -> Int# leFloat# Float# x Float# y)
expFloat, expm1Float :: Float -> Float logFloat, log1pFloat, sqrtFloat, fabsFloat :: Float -> Float sinFloat, cosFloat, tanFloat :: Float -> Float asinFloat, acosFloat, atanFloat :: Float -> Float sinhFloat, coshFloat, tanhFloat :: Float -> Float asinhFloat, acoshFloat, atanhFloat :: Float -> Float expFloat :: Float -> Float expFloat (F# Float# x) = Float# -> Float F# (Float# -> Float# expFloat# Float# x) expm1Float :: Float -> Float expm1Float (F# Float# x) = Float# -> Float F# (Float# -> Float# expm1Float# Float# x) logFloat :: Float -> Float logFloat (F# Float# x) = Float# -> Float F# (Float# -> Float# logFloat# Float# x) log1pFloat :: Float -> Float log1pFloat (F# Float# x) = Float# -> Float F# (Float# -> Float# log1pFloat# Float# x) sqrtFloat :: Float -> Float sqrtFloat (F# Float# x) = Float# -> Float F# (Float# -> Float# sqrtFloat# Float# x) fabsFloat :: Float -> Float fabsFloat (F# Float# x) = Float# -> Float F# (Float# -> Float# fabsFloat# Float# x) sinFloat :: Float -> Float sinFloat (F# Float# x) = Float# -> Float F# (Float# -> Float# sinFloat# Float# x) cosFloat :: Float -> Float cosFloat (F# Float# x) = Float# -> Float F# (Float# -> Float# cosFloat# Float# x) tanFloat :: Float -> Float tanFloat (F# Float# x) = Float# -> Float F# (Float# -> Float# tanFloat# Float# x) asinFloat :: Float -> Float asinFloat (F# Float# x) = Float# -> Float F# (Float# -> Float# asinFloat# Float# x) acosFloat :: Float -> Float acosFloat (F# Float# x) = Float# -> Float F# (Float# -> Float# acosFloat# Float# x) atanFloat :: Float -> Float atanFloat (F# Float# x) = Float# -> Float F# (Float# -> Float# atanFloat# Float# x) sinhFloat :: Float -> Float sinhFloat (F# Float# x) = Float# -> Float F# (Float# -> Float# sinhFloat# Float# x) coshFloat :: Float -> Float coshFloat (F# Float# x) = Float# -> Float F# (Float# -> Float# coshFloat# Float# x) tanhFloat :: Float -> Float tanhFloat (F# Float# x) = Float# -> Float F# (Float# -> Float# tanhFloat# Float# x) asinhFloat :: Float -> Float asinhFloat (F# Float# x) = Float# -> Float F# (Float# -> Float# asinhFloat# Float# x) acoshFloat :: Float -> Float acoshFloat (F# Float# x) = Float# -> Float F# (Float# -> Float# acoshFloat# Float# x) atanhFloat :: Float -> Float atanhFloat (F# Float# x) = Float# -> Float F# (Float# -> Float# atanhFloat# Float# x)
powerFloat :: Float -> Float -> Float powerFloat :: Float -> Float -> Float powerFloat (F# Float# x) (F# Float# y) = Float# -> Float F# (Float# -> Float# -> Float# powerFloat# Float# x Float# y)
plusDouble, minusDouble, timesDouble, divideDouble :: Double -> Double -> Double plusDouble :: Double -> Double -> Double plusDouble (D# Double# x) (D# Double# y) = Double# -> Double D# (Double# x Double# -> Double# -> Double# +## Double# y) minusDouble :: Double -> Double -> Double minusDouble (D# Double# x) (D# Double# y) = Double# -> Double D# (Double# x Double# -> Double# -> Double# -## Double# y) timesDouble :: Double -> Double -> Double timesDouble (D# Double# x) (D# Double# y) = Double# -> Double D# (Double# x Double# -> Double# -> Double# *## Double# y) divideDouble :: Double -> Double -> Double divideDouble (D# Double# x) (D# Double# y) = Double# -> Double D# (Double# x Double# -> Double# -> Double# /## Double# y)
negateDouble :: Double -> Double negateDouble :: Double -> Double negateDouble (D# Double# x) = Double# -> Double D# (Double# -> Double# negateDouble# Double# x)
gtDouble, geDouble, leDouble, ltDouble :: Double -> Double -> Bool gtDouble :: Double -> Double -> Bool gtDouble (D# Double# x) (D# Double# y) = Int# -> Bool isTrue# (Double# x Double# -> Double# -> Int# >## Double# y) geDouble :: Double -> Double -> Bool geDouble (D# Double# x) (D# Double# y) = Int# -> Bool isTrue# (Double# x Double# -> Double# -> Int# >=## Double# y) ltDouble :: Double -> Double -> Bool ltDouble (D# Double# x) (D# Double# y) = Int# -> Bool isTrue# (Double# x Double# -> Double# -> Int# <## Double# y) leDouble :: Double -> Double -> Bool leDouble (D# Double# x) (D# Double# y) = Int# -> Bool isTrue# (Double# x Double# -> Double# -> Int# <=## Double# y)
double2Float :: Double -> Float double2Float :: Double -> Float double2Float (D# Double# x) = Float# -> Float F# (Double# -> Float# double2Float# Double# x)
float2Double :: Float -> Double float2Double :: Float -> Double float2Double (F# Float# x) = Double# -> Double D# (Float# -> Double# float2Double# Float# x)
expDouble, expm1Double :: Double -> Double logDouble, log1pDouble, sqrtDouble, fabsDouble :: Double -> Double sinDouble, cosDouble, tanDouble :: Double -> Double asinDouble, acosDouble, atanDouble :: Double -> Double sinhDouble, coshDouble, tanhDouble :: Double -> Double asinhDouble, acoshDouble, atanhDouble :: Double -> Double expDouble :: Double -> Double expDouble (D# Double# x) = Double# -> Double D# (Double# -> Double# expDouble# Double# x) expm1Double :: Double -> Double expm1Double (D# Double# x) = Double# -> Double D# (Double# -> Double# expm1Double# Double# x) logDouble :: Double -> Double logDouble (D# Double# x) = Double# -> Double D# (Double# -> Double# logDouble# Double# x) log1pDouble :: Double -> Double log1pDouble (D# Double# x) = Double# -> Double D# (Double# -> Double# log1pDouble# Double# x) sqrtDouble :: Double -> Double sqrtDouble (D# Double# x) = Double# -> Double D# (Double# -> Double# sqrtDouble# Double# x) fabsDouble :: Double -> Double fabsDouble (D# Double# x) = Double# -> Double D# (Double# -> Double# fabsDouble# Double# x) sinDouble :: Double -> Double sinDouble (D# Double# x) = Double# -> Double D# (Double# -> Double# sinDouble# Double# x) cosDouble :: Double -> Double cosDouble (D# Double# x) = Double# -> Double D# (Double# -> Double# cosDouble# Double# x) tanDouble :: Double -> Double tanDouble (D# Double# x) = Double# -> Double D# (Double# -> Double# tanDouble# Double# x) asinDouble :: Double -> Double asinDouble (D# Double# x) = Double# -> Double D# (Double# -> Double# asinDouble# Double# x) acosDouble :: Double -> Double acosDouble (D# Double# x) = Double# -> Double D# (Double# -> Double# acosDouble# Double# x) atanDouble :: Double -> Double atanDouble (D# Double# x) = Double# -> Double D# (Double# -> Double# atanDouble# Double# x) sinhDouble :: Double -> Double sinhDouble (D# Double# x) = Double# -> Double D# (Double# -> Double# sinhDouble# Double# x) coshDouble :: Double -> Double coshDouble (D# Double# x) = Double# -> Double D# (Double# -> Double# coshDouble# Double# x) tanhDouble :: Double -> Double tanhDouble (D# Double# x) = Double# -> Double D# (Double# -> Double# tanhDouble# Double# x) asinhDouble :: Double -> Double asinhDouble (D# Double# x) = Double# -> Double D# (Double# -> Double# asinhDouble# Double# x) acoshDouble :: Double -> Double acoshDouble (D# Double# x) = Double# -> Double D# (Double# -> Double# acoshDouble# Double# x) atanhDouble :: Double -> Double atanhDouble (D# Double# x) = Double# -> Double D# (Double# -> Double# atanhDouble# Double# x)
powerDouble :: Double -> Double -> Double powerDouble :: Double -> Double -> Double powerDouble (D# Double# x) (D# Double# y) = Double# -> Double D# (Double# x Double# -> Double# -> Double# **## Double# y)
foreign import ccall unsafe "isFloatNaN" isFloatNaN :: Float -> Int foreign import ccall unsafe "isFloatInfinite" isFloatInfinite :: Float -> Int foreign import ccall unsafe "isFloatDenormalized" isFloatDenormalized :: Float -> Int foreign import ccall unsafe "isFloatNegativeZero" isFloatNegativeZero :: Float -> Int foreign import ccall unsafe "isFloatFinite" isFloatFinite :: Float -> Int
foreign import ccall unsafe "isDoubleNaN" isDoubleNaN :: Double -> Int foreign import ccall unsafe "isDoubleInfinite" isDoubleInfinite :: Double -> Int foreign import ccall unsafe "isDoubleDenormalized" isDoubleDenormalized :: Double -> Int foreign import ccall unsafe "isDoubleNegativeZero" isDoubleNegativeZero :: Double -> Int foreign import ccall unsafe "isDoubleFinite" isDoubleFinite :: Double -> Int
word2Double :: Word -> Double word2Double :: Word -> Double word2Double (W# Word# w) = Double# -> Double D# (Word# -> Double# word2Double# Word# w)
word2Float :: Word -> Float word2Float :: Word -> Float word2Float (W# Word# w) = Float# -> Float F# (Word# -> Float# word2Float# Word# w)
{-# RULES "realToFrac/Float->Float" realToFrac = id :: Float -> Float "realToFrac/Float->Double" realToFrac = float2Double "realToFrac/Double->Float" realToFrac = double2Float "realToFrac/Double->Double" realToFrac = id :: Double -> Double "realToFrac/Int->Double" realToFrac = int2Double -- See Note [realToFrac int-to-float] "realToFrac/Int->Float" realToFrac = int2Float -- ..ditto #-}
showSignedFloat :: (RealFloat a)
=> (a -> ShowS)
-> Int
-> a
-> ShowS
showSignedFloat :: forall a. RealFloat a => (a -> ShowS) -> Int -> a -> ShowS
showSignedFloat a -> ShowS
showPos Int
p a
x
| a
x a -> a -> Bool
forall a. Ord a => a -> a -> Bool
< a
0 Bool -> Bool -> Bool
|| a -> Bool
forall a. RealFloat a => a -> Bool
isNegativeZero a
x
= Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
6) (Char -> ShowS
showChar Char
'-' ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> ShowS
showPos (-a
x))
| Bool
otherwise = a -> ShowS
showPos a
x
clamp :: Int -> Int -> Int clamp :: Int -> Int -> Int clamp Int bd Int k = Int -> Int -> Int forall a. Ord a => a -> a -> a max (-Int bd) (Int -> Int -> Int forall a. Ord a => a -> a -> a min Int bd Int k)
{-# INLINE castWord32ToFloat #-} castWord32ToFloat :: Word32 -> Float castWord32ToFloat :: Word32 -> Float castWord32ToFloat (W32# Word32# w#) = Float# -> Float F# (Word32# -> Float# stgWord32ToFloat Word32# w#)
foreign import prim "stg_word32ToFloatzh" stgWord32ToFloat :: Word32# -> Float#
{-# INLINE castFloatToWord32 #-} castFloatToWord32 :: Float -> Word32 castFloatToWord32 :: Float -> Word32 castFloatToWord32 (F# Float# f#) = Word32# -> Word32 W32# (Float# -> Word32# stgFloatToWord32 Float# f#)
foreign import prim "stg_floatToWord32zh" stgFloatToWord32 :: Float# -> Word32#
{-# INLINE castWord64ToDouble #-} castWord64ToDouble :: Word64 -> Double castWord64ToDouble :: Word64 -> Double castWord64ToDouble (W64# Word# w) = Double# -> Double D# (Word# -> Double# stgWord64ToDouble Word# w)
foreign import prim "stg_word64ToDoublezh" #if WORD_SIZE_IN_BITS == 64 stgWord64ToDouble :: Word# -> Double# #else stgWord64ToDouble :: Word64# -> Double# #endif
{-# INLINE castDoubleToWord64 #-} castDoubleToWord64 :: Double -> Word64 castDoubleToWord64 :: Double -> Word64 castDoubleToWord64 (D# Double# d#) = Word# -> Word64 W64# (Double# -> Word# stgDoubleToWord64 Double# d#)
foreign import prim "stg_doubleToWord64zh" #if WORD_SIZE_IN_BITS == 64 stgDoubleToWord64 :: Double# -> Word# #else stgDoubleToWord64 :: Double# -> Word64# #endif