-- | Extra numeric functions - formatting and specialised conversions.
module Numeric.Extra(
    module Numeric,
    showDP,
    intToDouble, intToFloat, floatToDouble, doubleToFloat
    ) where

import Numeric


---------------------------------------------------------------------
-- Data.String

-- | Show a number to a fixed number of decimal places.
--
-- > showDP 4 pi == "3.1416"
-- > showDP 0 pi == "3"
-- > showDP 2 3  == "3.00"
showDP :: RealFloat a => Int -> a -> String
showDP :: Int -> a -> String
showDP Int
n a
x = Maybe Int -> a -> ShowS
forall a. RealFloat a => Maybe Int -> a -> ShowS
showFFloat (Int -> Maybe Int
forall a. a -> Maybe a
Just Int
n) a
x String
""


---------------------------------------------------------------------
-- Numeric

-- | Specialised numeric conversion, type restricted version of 'fromIntegral'.
intToDouble :: Int -> Double
intToDouble :: Int -> Double
intToDouble = Int -> Double
forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Specialised numeric conversion, type restricted version of 'fromIntegral'.
intToFloat :: Int -> Float
intToFloat :: Int -> Float
intToFloat = Int -> Float
forall a b. (Integral a, Num b) => a -> b
fromIntegral

-- | Specialised numeric conversion, type restricted version of 'realToFrac'.
floatToDouble :: Float -> Double
floatToDouble :: Float -> Double
floatToDouble = Float -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac

-- | Specialised numeric conversion, type restricted version of 'realToFrac'.
doubleToFloat :: Double -> Float
doubleToFloat :: Double -> Float
doubleToFloat = Double -> Float
forall a b. (Real a, Fractional b) => a -> b
realToFrac