{-# LANGUAGE HexFloatLiterals #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Numeric.Rounded.Hardware.Internal.Conversion
( fromInt
, fromIntF
, intervalFromInteger_default
, fromRatio
, fromRatioF
, intervalFromRational_default
) where
import Numeric.Rounded.Hardware.Internal.Rounding
import Numeric.Rounded.Hardware.Internal.RoundedResult
import Numeric.Rounded.Hardware.Internal.FloatUtil
import Data.Bits
import Data.Functor.Product
import Math.NumberTheory.Logarithms (integerLog2')
import Data.Ratio
import Control.Exception (assert)
intervalFromInteger_default :: RealFloat a => Integer -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
intervalFromInteger_default x = case fromIntF x of Pair a b -> (a, b)
{-# SPECIALIZE intervalFromInteger_default :: Integer -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float) #-}
{-# SPECIALIZE intervalFromInteger_default :: Integer -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double) #-}
intervalFromRational_default :: RealFloat a => Rational -> (Rounded 'TowardNegInf a, Rounded 'TowardInf a)
intervalFromRational_default x = case fromRatioF (numerator x) (denominator x) of Pair a b -> (a, b)
{-# SPECIALIZE intervalFromRational_default :: Rational -> (Rounded 'TowardNegInf Float, Rounded 'TowardInf Float) #-}
{-# SPECIALIZE intervalFromRational_default :: Rational -> (Rounded 'TowardNegInf Double, Rounded 'TowardInf Double) #-}
fromInt :: RealFloat a => RoundingMode -> Integer -> a
fromInt r n = withRoundingMode (fromIntF n) r
{-# SPECIALIZE fromInt :: RoundingMode -> Integer -> Float #-}
{-# SPECIALIZE fromInt :: RoundingMode -> Integer -> Double #-}
fromIntF :: forall a f. (RealFloat a, Result f) => Integer -> f a
fromIntF !_ | floatRadix (undefined :: a) /= 2 = error "radix other than 2 is not supported"
fromIntF 0 = exact 0
fromIntF n | n < 0 = negate <$> withOppositeRoundingMode (fromPositiveIntF (- n))
| otherwise = fromPositiveIntF n
{-# INLINE fromIntF #-}
fromPositiveIntF :: forall a f. (RealFloat a, Result f) => Integer -> f a
fromPositiveIntF !n
= let !k = integerLog2' n
!fDigits = floatDigits (undefined :: a)
in if k < fDigits
then exact (fromInteger n)
else let e = k - (fDigits - 1)
q = n `unsafeShiftR` e
r = n .&. ((1 `unsafeShiftL` e) - 1)
(_expMin, !expMax) = floatRange (undefined :: a)
in if k >= expMax
then
inexact (1 / 0)
(1 / 0)
maxFinite_ieee
maxFinite_ieee
else
if r == 0
then exact $ encodeFloat q e
else
let down = encodeFloat q e
up = encodeFloat (q + 1) e
toNearest = case compare r (1 `unsafeShiftL` (e-1)) of
LT -> down
EQ | even q -> down
| otherwise -> up
GT -> up
in inexact toNearest up down down
{-# SPECIALIZE fromPositiveIntF :: Integer -> DynamicRoundingMode Float #-}
{-# SPECIALIZE fromPositiveIntF :: Integer -> OppositeRoundingMode DynamicRoundingMode Float #-}
{-# SPECIALIZE fromPositiveIntF :: Rounding r => Integer -> Rounded r Float #-}
{-# SPECIALIZE fromPositiveIntF :: Rounding r => Integer -> OppositeRoundingMode (Rounded r) Float #-}
{-# SPECIALIZE fromPositiveIntF :: Integer -> Product (Rounded 'TowardNegInf) (Rounded 'TowardInf) Float #-}
{-# SPECIALIZE fromPositiveIntF :: Integer -> OppositeRoundingMode (Product (Rounded 'TowardNegInf) (Rounded 'TowardInf)) Float #-}
{-# SPECIALIZE fromPositiveIntF :: Integer -> DynamicRoundingMode Double #-}
{-# SPECIALIZE fromPositiveIntF :: Integer -> OppositeRoundingMode DynamicRoundingMode Double #-}
{-# SPECIALIZE fromPositiveIntF :: Rounding r => Integer -> Rounded r Double #-}
{-# SPECIALIZE fromPositiveIntF :: Rounding r => Integer -> OppositeRoundingMode (Rounded r) Double #-}
{-# SPECIALIZE fromPositiveIntF :: Integer -> Product (Rounded 'TowardNegInf) (Rounded 'TowardInf) Double #-}
{-# SPECIALIZE fromPositiveIntF :: Integer -> OppositeRoundingMode (Product (Rounded 'TowardNegInf) (Rounded 'TowardInf)) Double #-}
fromRatio :: (RealFloat a)
=> RoundingMode
-> Integer
-> Integer
-> a
fromRatio r n d = withRoundingMode (fromRatioF n d) r
{-# SPECIALIZE fromRatio :: RoundingMode -> Integer -> Integer -> Float #-}
{-# SPECIALIZE fromRatio :: RoundingMode -> Integer -> Integer -> Double #-}
fromRatioF :: forall a f. (RealFloat a, Result f)
=> Integer
-> Integer
-> f a
fromRatioF !_ !_ | floatRadix (undefined :: a) /= 2 = error "radix other than 2 is not supported"
fromRatioF 0 _ = exact 0
fromRatioF n 0 | n > 0 = exact (1 / 0)
| otherwise = exact (- 1 / 0)
fromRatioF n d | d < 0 = error "fromRatio: negative denominator"
| n < 0 = negate <$> withOppositeRoundingMode (fromPositiveRatioF (- n) d)
| otherwise = fromPositiveRatioF n d
{-# INLINE fromRatioF #-}
fromPositiveRatioF :: forall a f. (RealFloat a, Result f)
=> Integer -> Integer -> f a
fromPositiveRatioF !n !d
= let ln, ld, e :: Int
ln = integerLog2' n
ld = integerLog2' d
e = ln - ld - fDigits
q, r, d_ :: Integer
d_ | e >= 0 = d `unsafeShiftL` e
| otherwise = d
(!q, !r) | e >= 0 = n `quotRem` d_
| otherwise = (n `unsafeShiftL` (-e)) `quotRem` d
q', r', d' :: Integer
e' :: Int
(!q', !r', !d', !e') | q < (1 `unsafeShiftL` fDigits) = (q, r, d_, e)
| otherwise = let (q'', r'') = q `quotRem` 2
in (q'', r'' * d_ + r, 2 * d_, e + 1)
in assert (n % d * 2^^(-e) == fromInteger q + r % d_) $
assert (n % d * 2^^(-e') == fromInteger q' + r' % d') $
if expMin <= e' + fDigits && e' + fDigits <= expMax
then
if r' == 0
then
exact $ encodeFloat q' e'
else
let down = encodeFloat q' e'
up = encodeFloat (q' + 1) e'
toNearest = case compare (2 * r') d' of
LT -> down
EQ | even q' -> down
| otherwise -> up
GT -> up
in inexact toNearest up down down
else
if expMax <= e' + fDigits
then
inexact (1 / 0)
(1 / 0)
maxFinite_ieee
maxFinite_ieee
else
let (!q'', !r'') = q' `quotRem` (1 `unsafeShiftL` (expMin - fDigits - e'))
in if r' == 0 && r'' == 0
then exact $ encodeFloat q'' (expMin - fDigits)
else let down = encodeFloat q'' (expMin - fDigits)
up = encodeFloat (q'' + 1) (expMin - fDigits)
toNearest = case compare r'' (1 `unsafeShiftL` (expMin - fDigits - e' - 1)) of
LT -> down
GT -> up
EQ | r' /= 0 -> up
| even q' -> down
| otherwise -> up
in inexact toNearest up down down
where
!fDigits = floatDigits (undefined :: a)
(!expMin, !expMax) = floatRange (undefined :: a)
{-# SPECIALIZE fromPositiveRatioF :: Integer -> Integer -> DynamicRoundingMode Float #-}
{-# SPECIALIZE fromPositiveRatioF :: Integer -> Integer -> OppositeRoundingMode DynamicRoundingMode Float #-}
{-# SPECIALIZE fromPositiveRatioF :: Rounding r => Integer -> Integer -> Rounded r Float #-}
{-# SPECIALIZE fromPositiveRatioF :: Rounding r => Integer -> Integer -> OppositeRoundingMode (Rounded r) Float #-}
{-# SPECIALIZE fromPositiveRatioF :: Integer -> Integer -> Product (Rounded 'TowardNegInf) (Rounded 'TowardInf) Float #-}
{-# SPECIALIZE fromPositiveRatioF :: Integer -> Integer -> OppositeRoundingMode (Product (Rounded 'TowardNegInf) (Rounded 'TowardInf)) Float #-}
{-# SPECIALIZE fromPositiveRatioF :: Integer -> Integer -> DynamicRoundingMode Double #-}
{-# SPECIALIZE fromPositiveRatioF :: Integer -> Integer -> OppositeRoundingMode DynamicRoundingMode Double #-}
{-# SPECIALIZE fromPositiveRatioF :: Rounding r => Integer -> Integer -> Rounded r Double #-}
{-# SPECIALIZE fromPositiveRatioF :: Rounding r => Integer -> Integer -> OppositeRoundingMode (Rounded r) Double #-}
{-# SPECIALIZE fromPositiveRatioF :: Integer -> Integer -> Product (Rounded 'TowardNegInf) (Rounded 'TowardInf) Double #-}
{-# SPECIALIZE fromPositiveRatioF :: Integer -> Integer -> OppositeRoundingMode (Product (Rounded 'TowardNegInf) (Rounded 'TowardInf)) Double #-}