{-# LANGUAGE RebindableSyntax #-}
module Algebra.ToRational where
import qualified Algebra.ZeroTestable as ZeroTestable
import qualified Algebra.Field as Field
import qualified Algebra.Absolute as Absolute
import Algebra.Field (fromRational, )
import Algebra.Ring (fromInteger, )
import Number.Ratio (Rational, )
import Data.Int (Int, Int8, Int16, Int32, Int64, )
import Data.Word (Word, Word8, Word16, Word32, Word64, )
import qualified Prelude as P
import NumericPrelude.Base
import Prelude (Integer, Float, Double, )
class (Absolute.C a, ZeroTestable.C a, Ord a) => C a where
toRational :: a -> Rational
instance C Integer where
{-# INLINE toRational #-}
toRational :: Integer -> Rational
toRational = Integer -> Rational
forall a. C a => Integer -> a
fromInteger
instance C Float where
{-# INLINE toRational #-}
toRational :: Float -> Rational
toRational = Rational -> Rational
forall a. C a => Rational -> a
fromRational (Rational -> Rational) -> (Float -> Rational) -> Float -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Rational
forall a. Real a => a -> Rational
P.toRational
instance C Double where
{-# INLINE toRational #-}
toRational :: Double -> Rational
toRational = Rational -> Rational
forall a. C a => Rational -> a
fromRational (Rational -> Rational)
-> (Double -> Rational) -> Double -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Rational
forall a. Real a => a -> Rational
P.toRational
instance C Int where {-# INLINE toRational #-}; toRational :: Int -> Rational
toRational = Integer -> Rational
forall a. C a => a -> Rational
toRational (Integer -> Rational) -> (Int -> Integer) -> Int -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> Integer
forall a. Integral a => a -> Integer
P.toInteger
instance C Int8 where {-# INLINE toRational #-}; toRational :: Int8 -> Rational
toRational = Integer -> Rational
forall a. C a => a -> Rational
toRational (Integer -> Rational) -> (Int8 -> Integer) -> Int8 -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int8 -> Integer
forall a. Integral a => a -> Integer
P.toInteger
instance C Int16 where {-# INLINE toRational #-}; toRational :: Int16 -> Rational
toRational = Integer -> Rational
forall a. C a => a -> Rational
toRational (Integer -> Rational) -> (Int16 -> Integer) -> Int16 -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int16 -> Integer
forall a. Integral a => a -> Integer
P.toInteger
instance C Int32 where {-# INLINE toRational #-}; toRational :: Int32 -> Rational
toRational = Integer -> Rational
forall a. C a => a -> Rational
toRational (Integer -> Rational) -> (Int32 -> Integer) -> Int32 -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> Integer
forall a. Integral a => a -> Integer
P.toInteger
instance C Int64 where {-# INLINE toRational #-}; toRational :: Int64 -> Rational
toRational = Integer -> Rational
forall a. C a => a -> Rational
toRational (Integer -> Rational) -> (Int64 -> Integer) -> Int64 -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Integer
forall a. Integral a => a -> Integer
P.toInteger
instance C Word where {-# INLINE toRational #-}; toRational :: Word -> Rational
toRational = Integer -> Rational
forall a. C a => a -> Rational
toRational (Integer -> Rational) -> (Word -> Integer) -> Word -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word -> Integer
forall a. Integral a => a -> Integer
P.toInteger
instance C Word8 where {-# INLINE toRational #-}; toRational :: Word8 -> Rational
toRational = Integer -> Rational
forall a. C a => a -> Rational
toRational (Integer -> Rational) -> (Word8 -> Integer) -> Word8 -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word8 -> Integer
forall a. Integral a => a -> Integer
P.toInteger
instance C Word16 where {-# INLINE toRational #-}; toRational :: Word16 -> Rational
toRational = Integer -> Rational
forall a. C a => a -> Rational
toRational (Integer -> Rational) -> (Word16 -> Integer) -> Word16 -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Integer
forall a. Integral a => a -> Integer
P.toInteger
instance C Word32 where {-# INLINE toRational #-}; toRational :: Word32 -> Rational
toRational = Integer -> Rational
forall a. C a => a -> Rational
toRational (Integer -> Rational) -> (Word32 -> Integer) -> Word32 -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> Integer
forall a. Integral a => a -> Integer
P.toInteger
instance C Word64 where {-# INLINE toRational #-}; toRational :: Word64 -> Rational
toRational = Integer -> Rational
forall a. C a => a -> Rational
toRational (Integer -> Rational) -> (Word64 -> Integer) -> Word64 -> Rational
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Integer
forall a. Integral a => a -> Integer
P.toInteger
{-# NOINLINE [2] realToField #-}
realToField :: (C a, Field.C b) => a -> b
realToField :: a -> b
realToField = Rational -> b
forall a. C a => Rational -> a
Field.fromRational' (Rational -> b) -> (a -> Rational) -> a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> Rational
forall a. C a => a -> Rational
toRational
{-# RULES
"NP.realToField :: Integer -> Float " realToField = P.realToFrac :: Integer -> Float ;
"NP.realToField :: Int -> Float " realToField = P.realToFrac :: Int -> Float ;
"NP.realToField :: Int8 -> Float " realToField = P.realToFrac :: Int8 -> Float ;
"NP.realToField :: Int16 -> Float " realToField = P.realToFrac :: Int16 -> Float ;
"NP.realToField :: Int32 -> Float " realToField = P.realToFrac :: Int32 -> Float ;
"NP.realToField :: Int64 -> Float " realToField = P.realToFrac :: Int64 -> Float ;
"NP.realToField :: Word -> Float " realToField = P.realToFrac :: Word -> Float ;
"NP.realToField :: Word8 -> Float " realToField = P.realToFrac :: Word8 -> Float ;
"NP.realToField :: Word16 -> Float " realToField = P.realToFrac :: Word16 -> Float ;
"NP.realToField :: Word32 -> Float " realToField = P.realToFrac :: Word32 -> Float ;
"NP.realToField :: Word64 -> Float " realToField = P.realToFrac :: Word64 -> Float ;
"NP.realToField :: Float -> Float " realToField = P.realToFrac :: Float -> Float ;
"NP.realToField :: Double -> Float " realToField = P.realToFrac :: Double -> Float ;
"NP.realToField :: Integer -> Double" realToField = P.realToFrac :: Integer -> Double;
"NP.realToField :: Int -> Double" realToField = P.realToFrac :: Int -> Double;
"NP.realToField :: Int8 -> Double" realToField = P.realToFrac :: Int8 -> Double;
"NP.realToField :: Int16 -> Double" realToField = P.realToFrac :: Int16 -> Double;
"NP.realToField :: Int32 -> Double" realToField = P.realToFrac :: Int32 -> Double;
"NP.realToField :: Int64 -> Double" realToField = P.realToFrac :: Int64 -> Double;
"NP.realToField :: Word -> Double" realToField = P.realToFrac :: Word -> Double;
"NP.realToField :: Word8 -> Double" realToField = P.realToFrac :: Word8 -> Double;
"NP.realToField :: Word16 -> Double" realToField = P.realToFrac :: Word16 -> Double;
"NP.realToField :: Word32 -> Double" realToField = P.realToFrac :: Word32 -> Double;
"NP.realToField :: Word64 -> Double" realToField = P.realToFrac :: Word64 -> Double;
"NP.realToField :: Float -> Double" realToField = P.realToFrac :: Float -> Double;
"NP.realToField :: Double -> Double" realToField = P.realToFrac :: Double -> Double;
#-}