{-# LANGUAGE DefaultSignatures, InstanceSigs, MagicHash, MultiParamTypeClasses,
             TypeFamilies #-}

-- |
-- Module      : Data.Double.Conversion.Convertable
-- Copyright   : (c) 2011 MailRank, Inc.
--
-- License     : BSD-style
-- Maintainer  : bos@serpentine.com
-- Stability   : experimental
-- Portability : GHC

module Data.Double.Conversion.Convertable
    ( Convertable(..)
    ) where
import Data.ByteString.Builder.Prim (primBounded)
import Data.Text (Text)

import Data.Double.Conversion.Internal.FFI
import Data.String (IsString)

import qualified Data.ByteString.Builder as BB (Builder)
import qualified Data.ByteString.Internal as B (ByteString(..))
import qualified Data.Double.Conversion.Internal.ByteString as CB (convert)
import qualified Data.Double.Conversion.Internal.ByteStringBuilder as CBB (convert)
import qualified Data.Double.Conversion.Internal.Text as CT (convert)
import qualified Data.Double.Conversion.Internal.TextBuilder as CTB (convert)
import qualified Data.Text.Internal.Builder as T (Builder)

-- | Type class for floating data types, that cen be converted, using double-conversion library
--
-- Default instanced convert input to Double and then make Bytestring Builder from it.
--
-- list of functions :
--
-- toExponential:
-- Compute a representation in exponential format with the requested
-- number of digits after the decimal point. The last emitted digit is
-- rounded.  If -1 digits are requested, then the shortest exponential
-- representation is computed.
--
-- toPrecision:
-- Compute @precision@ leading digits of the given value either in
-- exponential or decimal format. The last computed digit is rounded.
--
-- toFixed:
-- Compute a decimal representation with a fixed number of digits
-- after the decimal point. The last emitted digit is rounded.
--
-- toShortest:
-- Compute the shortest string of digits that correctly represent
-- the input number.
--
-- Conversion to text is twice faster than conversion to bytestring
-- Conversion to text via Builder (both in the in case of bytestring and text) in case of single number
-- is much slower, than to text or bytestring directly. (2-3x)
-- But conversion large amount of numbers to text via Builder is much faster than directly (up to 50x).
-- Conversion to text via text builder is a little slower, then via bytestring builder

class (RealFloat a, IsString b) => Convertable a b where
  toExponential :: Int -> a -> b
  default toExponential :: (b ~ BB.Builder) => Int -> a -> b
  toExponential Int
ndigits a
num = BoundedPrim Double -> Double -> Builder
forall a. BoundedPrim a -> a -> Builder
primBounded (String
-> CInt -> (CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> BoundedPrim a
CBB.convert String
"toExponential" CInt
len ((CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double)
-> (CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double
forall a b. (a -> b) -> a -> b
$ \CDouble
val Ptr Word8
mba ->
                        CDouble -> Ptr Word8 -> CInt -> IO CInt
c_ToExponential CDouble
val Ptr Word8
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)) (a -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac a
num :: Double)
      where len :: CInt
len = CInt
c_ToExponentialLength
            {-# NOINLINE len #-}

  toPrecision :: Int -> a -> b
  default toPrecision :: (b ~ BB.Builder) => Int -> a -> b
  toPrecision Int
ndigits a
num = BoundedPrim Double -> Double -> Builder
forall a. BoundedPrim a -> a -> Builder
primBounded (String
-> CInt -> (CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> BoundedPrim a
CBB.convert String
"toPrecision" CInt
len ((CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double)
-> (CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double
forall a b. (a -> b) -> a -> b
$ \CDouble
val Ptr Word8
mba ->
                      CDouble -> Ptr Word8 -> CInt -> IO CInt
c_ToPrecision CDouble
val Ptr Word8
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)) (a -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac a
num :: Double)
      where len :: CInt
len = CInt
c_ToPrecisionLength
            {-# NOINLINE len #-}

  toFixed :: Int -> a -> b
  default toFixed :: (b ~ BB.Builder) => Int -> a -> b
  toFixed Int
ndigits a
num = BoundedPrim Double -> Double -> Builder
forall a. BoundedPrim a -> a -> Builder
primBounded (String
-> CInt -> (CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> BoundedPrim a
CBB.convert String
"toFixed" CInt
len ((CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double)
-> (CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double
forall a b. (a -> b) -> a -> b
$ \CDouble
val Ptr Word8
mba ->
                  CDouble -> Ptr Word8 -> CInt -> IO CInt
c_ToFixed CDouble
val Ptr Word8
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)) (a -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac a
num :: Double)
      where len :: CInt
len = CInt
c_ToFixedLength
            {-# NOINLINE len #-}

  toShortest :: a -> b
  default toShortest :: (b ~ BB.Builder) => a -> b
  toShortest a
num = BoundedPrim Double -> Double -> Builder
forall a. BoundedPrim a -> a -> Builder
primBounded (String
-> CInt -> (CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> BoundedPrim a
CBB.convert String
"toShortest" CInt
len CDouble -> Ptr Word8 -> IO CInt
c_ToShortest) (a -> Double
forall a b. (Real a, Fractional b) => a -> b
realToFrac a
num :: Double)
      where len :: CInt
len = CInt
c_ToShortestLength
            {-# NOINLINE len #-}

-- Instances

instance Convertable Double BB.Builder where
    toExponential :: Int -> Double -> BB.Builder
    toExponential :: Int -> Double -> Builder
toExponential Int
ndigits = BoundedPrim Double -> Double -> Builder
forall a. BoundedPrim a -> a -> Builder
primBounded (BoundedPrim Double -> Double -> Builder)
-> BoundedPrim Double -> Double -> Builder
forall a b. (a -> b) -> a -> b
$ String
-> CInt -> (CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> BoundedPrim a
CBB.convert String
"toExponential" CInt
len ((CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double)
-> (CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double
forall a b. (a -> b) -> a -> b
$ \CDouble
val Ptr Word8
mba ->
                        CDouble -> Ptr Word8 -> CInt -> IO CInt
c_ToExponential CDouble
val Ptr Word8
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToExponentialLength
              {-# NOINLINE len #-}

    toPrecision :: Int -> Double -> BB.Builder
    toPrecision :: Int -> Double -> Builder
toPrecision Int
ndigits = BoundedPrim Double -> Double -> Builder
forall a. BoundedPrim a -> a -> Builder
primBounded (String
-> CInt -> (CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> BoundedPrim a
CBB.convert String
"toPrecision" CInt
len ((CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double)
-> (CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double
forall a b. (a -> b) -> a -> b
$ \CDouble
val Ptr Word8
mba ->
                      CDouble -> Ptr Word8 -> CInt -> IO CInt
c_ToPrecision CDouble
val Ptr Word8
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits))
        where len :: CInt
len = CInt
c_ToPrecisionLength
              {-# NOINLINE len #-}

    toShortest :: Double -> BB.Builder
    toShortest :: Double -> Builder
toShortest = BoundedPrim Double -> Double -> Builder
forall a. BoundedPrim a -> a -> Builder
primBounded (BoundedPrim Double -> Double -> Builder)
-> BoundedPrim Double -> Double -> Builder
forall a b. (a -> b) -> a -> b
$ String
-> CInt -> (CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> BoundedPrim a
CBB.convert String
"toShortest" CInt
len CDouble -> Ptr Word8 -> IO CInt
c_ToShortest
        where len :: CInt
len = CInt
c_ToShortestLength
              {-# NOINLINE len #-}

    toFixed :: Int -> Double -> BB.Builder
    toFixed :: Int -> Double -> Builder
toFixed Int
ndigits = BoundedPrim Double -> Double -> Builder
forall a. BoundedPrim a -> a -> Builder
primBounded (BoundedPrim Double -> Double -> Builder)
-> BoundedPrim Double -> Double -> Builder
forall a b. (a -> b) -> a -> b
$ String
-> CInt -> (CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> BoundedPrim a
CBB.convert String
"toFixed" CInt
len ((CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double)
-> (CDouble -> Ptr Word8 -> IO CInt) -> BoundedPrim Double
forall a b. (a -> b) -> a -> b
$ \CDouble
val Ptr Word8
mba ->
                  CDouble -> Ptr Word8 -> CInt -> IO CInt
c_ToFixed CDouble
val Ptr Word8
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToFixedLength
              {-# NOINLINE len #-}


instance Convertable Float BB.Builder where
    toExponential :: Int -> Float -> BB.Builder
    toExponential :: Int -> Float -> Builder
toExponential Int
ndigits = BoundedPrim Float -> Float -> Builder
forall a. BoundedPrim a -> a -> Builder
primBounded (BoundedPrim Float -> Float -> Builder)
-> BoundedPrim Float -> Float -> Builder
forall a b. (a -> b) -> a -> b
$ String
-> CInt -> (CFloat -> Ptr Word8 -> IO CInt) -> BoundedPrim Float
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> BoundedPrim a
CBB.convert String
"toExponential" CInt
len ((CFloat -> Ptr Word8 -> IO CInt) -> BoundedPrim Float)
-> (CFloat -> Ptr Word8 -> IO CInt) -> BoundedPrim Float
forall a b. (a -> b) -> a -> b
$ \CFloat
val Ptr Word8
mba ->
                        CFloat -> Ptr Word8 -> CInt -> IO CInt
c_ToExponentialFloat CFloat
val Ptr Word8
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToExponentialLength
              {-# NOINLINE len #-}

    toPrecision :: Int -> Float -> BB.Builder
    toPrecision :: Int -> Float -> Builder
toPrecision Int
ndigits = BoundedPrim Float -> Float -> Builder
forall a. BoundedPrim a -> a -> Builder
primBounded (String
-> CInt -> (CFloat -> Ptr Word8 -> IO CInt) -> BoundedPrim Float
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> BoundedPrim a
CBB.convert String
"toPrecision" CInt
len ((CFloat -> Ptr Word8 -> IO CInt) -> BoundedPrim Float)
-> (CFloat -> Ptr Word8 -> IO CInt) -> BoundedPrim Float
forall a b. (a -> b) -> a -> b
$ \CFloat
val Ptr Word8
mba ->
                      CFloat -> Ptr Word8 -> CInt -> IO CInt
c_ToPrecisionFloat CFloat
val Ptr Word8
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits))
        where len :: CInt
len = CInt
c_ToPrecisionLength
              {-# NOINLINE len #-}

    toShortest :: Float -> BB.Builder
    toShortest :: Float -> Builder
toShortest = BoundedPrim Float -> Float -> Builder
forall a. BoundedPrim a -> a -> Builder
primBounded (BoundedPrim Float -> Float -> Builder)
-> BoundedPrim Float -> Float -> Builder
forall a b. (a -> b) -> a -> b
$ String
-> CInt -> (CFloat -> Ptr Word8 -> IO CInt) -> BoundedPrim Float
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> BoundedPrim a
CBB.convert String
"toShortest" CInt
len CFloat -> Ptr Word8 -> IO CInt
c_ToShortestFloat
        where len :: CInt
len = CInt
c_ToShortestLength
              {-# NOINLINE len #-}

    toFixed :: Int -> Float -> BB.Builder
    toFixed :: Int -> Float -> Builder
toFixed Int
ndigits = BoundedPrim Float -> Float -> Builder
forall a. BoundedPrim a -> a -> Builder
primBounded (BoundedPrim Float -> Float -> Builder)
-> BoundedPrim Float -> Float -> Builder
forall a b. (a -> b) -> a -> b
$ String
-> CInt -> (CFloat -> Ptr Word8 -> IO CInt) -> BoundedPrim Float
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> BoundedPrim a
CBB.convert String
"toFixed" CInt
len ((CFloat -> Ptr Word8 -> IO CInt) -> BoundedPrim Float)
-> (CFloat -> Ptr Word8 -> IO CInt) -> BoundedPrim Float
forall a b. (a -> b) -> a -> b
$ \CFloat
val Ptr Word8
mba ->
                  CFloat -> Ptr Word8 -> CInt -> IO CInt
c_ToFixedFloat CFloat
val Ptr Word8
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToFixedLength
              {-# NOINLINE len #-}

-- Fast conversion to bytestring.
-- Although about 15 times faster than plain 'show', these functions
-- are /slower/ than their 'Text' counterparts, at roughly half the
-- speed.  (This seems to be due to the cost of allocating
-- 'ByteString' values via @malloc@.)

instance Convertable Double B.ByteString where
    toExponential :: Int -> Double -> B.ByteString
    toExponential :: Int -> Double -> ByteString
toExponential Int
ndigits = String
-> CInt
-> (CDouble -> Ptr Word8 -> IO CInt)
-> Double
-> ByteString
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> a -> ByteString
CB.convert String
"toExponential" CInt
len ((CDouble -> Ptr Word8 -> IO CInt) -> Double -> ByteString)
-> (CDouble -> Ptr Word8 -> IO CInt) -> Double -> ByteString
forall a b. (a -> b) -> a -> b
$ \CDouble
val Ptr Word8
mba ->
                        CDouble -> Ptr Word8 -> CInt -> IO CInt
c_ToExponential CDouble
val Ptr Word8
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToExponentialLength
              {-# NOINLINE len #-}

    toFixed :: Int -> Double -> B.ByteString
    toFixed :: Int -> Double -> ByteString
toFixed Int
ndigits = String
-> CInt
-> (CDouble -> Ptr Word8 -> IO CInt)
-> Double
-> ByteString
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> a -> ByteString
CB.convert String
"toFixed" CInt
len ((CDouble -> Ptr Word8 -> IO CInt) -> Double -> ByteString)
-> (CDouble -> Ptr Word8 -> IO CInt) -> Double -> ByteString
forall a b. (a -> b) -> a -> b
$ \CDouble
val Ptr Word8
mba ->
                  CDouble -> Ptr Word8 -> CInt -> IO CInt
c_ToFixed CDouble
val Ptr Word8
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToFixedLength
              {-# NOINLINE len #-}

    toShortest :: Double -> B.ByteString
    toShortest :: Double -> ByteString
toShortest = String
-> CInt
-> (CDouble -> Ptr Word8 -> IO CInt)
-> Double
-> ByteString
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> a -> ByteString
CB.convert String
"toShortest" CInt
len CDouble -> Ptr Word8 -> IO CInt
c_ToShortest
        where len :: CInt
len = CInt
c_ToShortestLength
              {-# NOINLINE len #-}

    toPrecision :: Int -> Double -> B.ByteString
    toPrecision :: Int -> Double -> ByteString
toPrecision Int
ndigits = String
-> CInt
-> (CDouble -> Ptr Word8 -> IO CInt)
-> Double
-> ByteString
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> a -> ByteString
CB.convert String
"toPrecision" CInt
len ((CDouble -> Ptr Word8 -> IO CInt) -> Double -> ByteString)
-> (CDouble -> Ptr Word8 -> IO CInt) -> Double -> ByteString
forall a b. (a -> b) -> a -> b
$ \CDouble
val Ptr Word8
mba ->
                      CDouble -> Ptr Word8 -> CInt -> IO CInt
c_ToPrecision CDouble
val Ptr Word8
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToPrecisionLength
              {-# NOINLINE len #-}


instance Convertable Float B.ByteString where
    toExponential :: Int -> Float -> B.ByteString
    toExponential :: Int -> Float -> ByteString
toExponential Int
ndigits = String
-> CInt -> (CFloat -> Ptr Word8 -> IO CInt) -> Float -> ByteString
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> a -> ByteString
CB.convert String
"toExponential" CInt
len ((CFloat -> Ptr Word8 -> IO CInt) -> Float -> ByteString)
-> (CFloat -> Ptr Word8 -> IO CInt) -> Float -> ByteString
forall a b. (a -> b) -> a -> b
$ \CFloat
val Ptr Word8
mba ->
                        CFloat -> Ptr Word8 -> CInt -> IO CInt
c_ToExponentialFloat CFloat
val Ptr Word8
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToExponentialLength
              {-# NOINLINE len #-}

    toFixed :: Int -> Float -> B.ByteString
    toFixed :: Int -> Float -> ByteString
toFixed Int
ndigits = String
-> CInt -> (CFloat -> Ptr Word8 -> IO CInt) -> Float -> ByteString
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> a -> ByteString
CB.convert String
"toFixed" CInt
len ((CFloat -> Ptr Word8 -> IO CInt) -> Float -> ByteString)
-> (CFloat -> Ptr Word8 -> IO CInt) -> Float -> ByteString
forall a b. (a -> b) -> a -> b
$ \CFloat
val Ptr Word8
mba ->
                  CFloat -> Ptr Word8 -> CInt -> IO CInt
c_ToFixedFloat CFloat
val Ptr Word8
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToFixedLength
              {-# NOINLINE len #-}

    toShortest :: Float -> B.ByteString
    toShortest :: Float -> ByteString
toShortest = String
-> CInt -> (CFloat -> Ptr Word8 -> IO CInt) -> Float -> ByteString
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> a -> ByteString
CB.convert String
"toShortest" CInt
len CFloat -> Ptr Word8 -> IO CInt
c_ToShortestFloat
        where len :: CInt
len = CInt
c_ToShortestLength
              {-# NOINLINE len #-}

    toPrecision :: Int -> Float -> B.ByteString
    toPrecision :: Int -> Float -> ByteString
toPrecision Int
ndigits = String
-> CInt -> (CFloat -> Ptr Word8 -> IO CInt) -> Float -> ByteString
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String -> CInt -> (b -> Ptr Word8 -> IO CInt) -> a -> ByteString
CB.convert String
"toPrecision" CInt
len ((CFloat -> Ptr Word8 -> IO CInt) -> Float -> ByteString)
-> (CFloat -> Ptr Word8 -> IO CInt) -> Float -> ByteString
forall a b. (a -> b) -> a -> b
$ \CFloat
val Ptr Word8
mba ->
                      CFloat -> Ptr Word8 -> CInt -> IO CInt
c_ToPrecisionFloat CFloat
val Ptr Word8
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToPrecisionLength
              {-# NOINLINE len #-}


instance Convertable Double Text where
    toExponential :: Int -> Double -> Text
    toExponential :: Int -> Double -> Text
toExponential Int
ndigits = String
-> CInt
-> (forall s. CDouble -> MutableByteArray# s -> IO CInt)
-> Double
-> Text
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String
-> CInt
-> (forall s. b -> MutableByteArray# s -> IO CInt)
-> a
-> Text
CT.convert String
"toExponential" CInt
len ((forall s. CDouble -> MutableByteArray# s -> IO CInt)
 -> Double -> Text)
-> (forall s. CDouble -> MutableByteArray# s -> IO CInt)
-> Double
-> Text
forall a b. (a -> b) -> a -> b
$ \CDouble
val MutableByteArray# s
mba ->
                            CDouble -> MutableByteArray# s -> CInt -> IO CInt
forall s. CDouble -> MutableByteArray# s -> CInt -> IO CInt
c_Text_ToExponential CDouble
val MutableByteArray# s
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToExponentialLength
              {-# NOINLINE len #-}

    toFixed :: Int -> Double -> Text
    toFixed :: Int -> Double -> Text
toFixed Int
ndigits = String
-> CInt
-> (forall s. CDouble -> MutableByteArray# s -> IO CInt)
-> Double
-> Text
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String
-> CInt
-> (forall s. b -> MutableByteArray# s -> IO CInt)
-> a
-> Text
CT.convert String
"toFixed" CInt
len ((forall s. CDouble -> MutableByteArray# s -> IO CInt)
 -> Double -> Text)
-> (forall s. CDouble -> MutableByteArray# s -> IO CInt)
-> Double
-> Text
forall a b. (a -> b) -> a -> b
$ \CDouble
val MutableByteArray# s
mba ->
                    CDouble -> MutableByteArray# s -> CInt -> IO CInt
forall s. CDouble -> MutableByteArray# s -> CInt -> IO CInt
c_Text_ToFixed CDouble
val MutableByteArray# s
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToFixedLength
              {-# NOINLINE len #-}

    toShortest :: Double -> Text
    toShortest :: Double -> Text
toShortest = String
-> CInt
-> (forall s. CDouble -> MutableByteArray# s -> IO CInt)
-> Double
-> Text
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String
-> CInt
-> (forall s. b -> MutableByteArray# s -> IO CInt)
-> a
-> Text
CT.convert String
"toShortest" CInt
len forall s. CDouble -> MutableByteArray# s -> IO CInt
c_Text_ToShortest
        where len :: CInt
len = CInt
c_ToShortestLength
              {-# NOINLINE len #-}

    toPrecision :: Int -> Double -> Text
    toPrecision :: Int -> Double -> Text
toPrecision Int
ndigits = String
-> CInt
-> (forall s. CDouble -> MutableByteArray# s -> IO CInt)
-> Double
-> Text
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String
-> CInt
-> (forall s. b -> MutableByteArray# s -> IO CInt)
-> a
-> Text
CT.convert String
"toPrecision" CInt
len ((forall s. CDouble -> MutableByteArray# s -> IO CInt)
 -> Double -> Text)
-> (forall s. CDouble -> MutableByteArray# s -> IO CInt)
-> Double
-> Text
forall a b. (a -> b) -> a -> b
$ \CDouble
val MutableByteArray# s
mba ->
                          CDouble -> MutableByteArray# s -> CInt -> IO CInt
forall s. CDouble -> MutableByteArray# s -> CInt -> IO CInt
c_Text_ToPrecision CDouble
val MutableByteArray# s
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToPrecisionLength
              {-# NOINLINE len #-}


instance Convertable Float Text where
    toExponential :: Int -> Float -> Text
    toExponential :: Int -> Float -> Text
toExponential Int
ndigits = String
-> CInt
-> (forall s. CFloat -> MutableByteArray# s -> IO CInt)
-> Float
-> Text
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String
-> CInt
-> (forall s. b -> MutableByteArray# s -> IO CInt)
-> a
-> Text
CT.convert String
"toExponential" CInt
len ((forall s. CFloat -> MutableByteArray# s -> IO CInt)
 -> Float -> Text)
-> (forall s. CFloat -> MutableByteArray# s -> IO CInt)
-> Float
-> Text
forall a b. (a -> b) -> a -> b
$ \CFloat
val MutableByteArray# s
mba ->
                            CFloat -> MutableByteArray# s -> CInt -> IO CInt
forall s. CFloat -> MutableByteArray# s -> CInt -> IO CInt
c_Text_ToExponentialFloat CFloat
val MutableByteArray# s
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToExponentialLength
              {-# NOINLINE len #-}

    toFixed :: Int -> Float -> Text
    toFixed :: Int -> Float -> Text
toFixed Int
ndigits = String
-> CInt
-> (forall s. CFloat -> MutableByteArray# s -> IO CInt)
-> Float
-> Text
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String
-> CInt
-> (forall s. b -> MutableByteArray# s -> IO CInt)
-> a
-> Text
CT.convert String
"toFixed" CInt
len ((forall s. CFloat -> MutableByteArray# s -> IO CInt)
 -> Float -> Text)
-> (forall s. CFloat -> MutableByteArray# s -> IO CInt)
-> Float
-> Text
forall a b. (a -> b) -> a -> b
$ \CFloat
val MutableByteArray# s
mba ->
                    CFloat -> MutableByteArray# s -> CInt -> IO CInt
forall s. CFloat -> MutableByteArray# s -> CInt -> IO CInt
c_Text_ToFixedFloat CFloat
val MutableByteArray# s
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToFixedLength
              {-# NOINLINE len #-}

    toShortest :: Float -> Text
    toShortest :: Float -> Text
toShortest = String
-> CInt
-> (forall s. CFloat -> MutableByteArray# s -> IO CInt)
-> Float
-> Text
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String
-> CInt
-> (forall s. b -> MutableByteArray# s -> IO CInt)
-> a
-> Text
CT.convert String
"toShortest" CInt
len forall s. CFloat -> MutableByteArray# s -> IO CInt
c_Text_ToShortestFloat
        where len :: CInt
len = CInt
c_ToShortestLength
              {-# NOINLINE len #-}

    toPrecision :: Int -> Float -> Text
    toPrecision :: Int -> Float -> Text
toPrecision Int
ndigits = String
-> CInt
-> (forall s. CFloat -> MutableByteArray# s -> IO CInt)
-> Float
-> Text
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String
-> CInt
-> (forall s. b -> MutableByteArray# s -> IO CInt)
-> a
-> Text
CT.convert String
"toPrecision" CInt
len ((forall s. CFloat -> MutableByteArray# s -> IO CInt)
 -> Float -> Text)
-> (forall s. CFloat -> MutableByteArray# s -> IO CInt)
-> Float
-> Text
forall a b. (a -> b) -> a -> b
$ \CFloat
val MutableByteArray# s
mba ->
                          CFloat -> MutableByteArray# s -> CInt -> IO CInt
forall s. CFloat -> MutableByteArray# s -> CInt -> IO CInt
c_Text_ToPrecisionFloat CFloat
val MutableByteArray# s
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToPrecisionLength
              {-# NOINLINE len #-}


instance Convertable Double T.Builder where
    toExponential :: Int -> Double -> T.Builder
    toExponential :: Int -> Double -> Builder
toExponential Int
ndigits = String
-> CInt
-> (forall s. CDouble -> MutableByteArray# s -> IO CInt)
-> Double
-> Builder
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String
-> CInt
-> (forall s. b -> MutableByteArray# s -> IO CInt)
-> a
-> Builder
CTB.convert String
"toExponential" CInt
len ((forall s. CDouble -> MutableByteArray# s -> IO CInt)
 -> Double -> Builder)
-> (forall s. CDouble -> MutableByteArray# s -> IO CInt)
-> Double
-> Builder
forall a b. (a -> b) -> a -> b
$ \CDouble
val MutableByteArray# s
mba ->
                            CDouble -> MutableByteArray# s -> CInt -> IO CInt
forall s. CDouble -> MutableByteArray# s -> CInt -> IO CInt
c_Text_ToExponential CDouble
val MutableByteArray# s
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToExponentialLength
              {-# NOINLINE len #-}

    toFixed :: Int -> Double -> T.Builder
    toFixed :: Int -> Double -> Builder
toFixed Int
ndigits = String
-> CInt
-> (forall s. CDouble -> MutableByteArray# s -> IO CInt)
-> Double
-> Builder
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String
-> CInt
-> (forall s. b -> MutableByteArray# s -> IO CInt)
-> a
-> Builder
CTB.convert String
"toFixed" CInt
len ((forall s. CDouble -> MutableByteArray# s -> IO CInt)
 -> Double -> Builder)
-> (forall s. CDouble -> MutableByteArray# s -> IO CInt)
-> Double
-> Builder
forall a b. (a -> b) -> a -> b
$ \CDouble
val MutableByteArray# s
mba ->
                      CDouble -> MutableByteArray# s -> CInt -> IO CInt
forall s. CDouble -> MutableByteArray# s -> CInt -> IO CInt
c_Text_ToFixed CDouble
val MutableByteArray# s
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToFixedLength
              {-# NOINLINE len #-}

    toShortest :: Double -> T.Builder
    toShortest :: Double -> Builder
toShortest = String
-> CInt
-> (forall s. CDouble -> MutableByteArray# s -> IO CInt)
-> Double
-> Builder
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String
-> CInt
-> (forall s. b -> MutableByteArray# s -> IO CInt)
-> a
-> Builder
CTB.convert String
"toShortest" CInt
len forall s. CDouble -> MutableByteArray# s -> IO CInt
c_Text_ToShortest
        where len :: CInt
len = CInt
c_ToShortestLength
              {-# NOINLINE len #-}

    toPrecision :: Int -> Double -> T.Builder
    toPrecision :: Int -> Double -> Builder
toPrecision Int
ndigits = String
-> CInt
-> (forall s. CDouble -> MutableByteArray# s -> IO CInt)
-> Double
-> Builder
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String
-> CInt
-> (forall s. b -> MutableByteArray# s -> IO CInt)
-> a
-> Builder
CTB.convert String
"toPrecision" CInt
len ((forall s. CDouble -> MutableByteArray# s -> IO CInt)
 -> Double -> Builder)
-> (forall s. CDouble -> MutableByteArray# s -> IO CInt)
-> Double
-> Builder
forall a b. (a -> b) -> a -> b
$ \CDouble
val MutableByteArray# s
mba ->
                          CDouble -> MutableByteArray# s -> CInt -> IO CInt
forall s. CDouble -> MutableByteArray# s -> CInt -> IO CInt
c_Text_ToPrecision CDouble
val MutableByteArray# s
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToPrecisionLength
              {-# NOINLINE len #-}


instance Convertable Float T.Builder where
    toExponential :: Int -> Float -> T.Builder
    toExponential :: Int -> Float -> Builder
toExponential Int
ndigits = String
-> CInt
-> (forall s. CFloat -> MutableByteArray# s -> IO CInt)
-> Float
-> Builder
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String
-> CInt
-> (forall s. b -> MutableByteArray# s -> IO CInt)
-> a
-> Builder
CTB.convert String
"toExponential" CInt
len ((forall s. CFloat -> MutableByteArray# s -> IO CInt)
 -> Float -> Builder)
-> (forall s. CFloat -> MutableByteArray# s -> IO CInt)
-> Float
-> Builder
forall a b. (a -> b) -> a -> b
$ \CFloat
val MutableByteArray# s
mba ->
                            CFloat -> MutableByteArray# s -> CInt -> IO CInt
forall s. CFloat -> MutableByteArray# s -> CInt -> IO CInt
c_Text_ToExponentialFloat CFloat
val MutableByteArray# s
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToExponentialLength
              {-# NOINLINE len #-}

    toFixed :: Int -> Float -> T.Builder
    toFixed :: Int -> Float -> Builder
toFixed Int
ndigits = String
-> CInt
-> (forall s. CFloat -> MutableByteArray# s -> IO CInt)
-> Float
-> Builder
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String
-> CInt
-> (forall s. b -> MutableByteArray# s -> IO CInt)
-> a
-> Builder
CTB.convert String
"toFixed" CInt
len ((forall s. CFloat -> MutableByteArray# s -> IO CInt)
 -> Float -> Builder)
-> (forall s. CFloat -> MutableByteArray# s -> IO CInt)
-> Float
-> Builder
forall a b. (a -> b) -> a -> b
$ \CFloat
val MutableByteArray# s
mba ->
                      CFloat -> MutableByteArray# s -> CInt -> IO CInt
forall s. CFloat -> MutableByteArray# s -> CInt -> IO CInt
c_Text_ToFixedFloat CFloat
val MutableByteArray# s
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToFixedLength
              {-# NOINLINE len #-}

    toShortest :: Float -> T.Builder
    toShortest :: Float -> Builder
toShortest = String
-> CInt
-> (forall s. CFloat -> MutableByteArray# s -> IO CInt)
-> Float
-> Builder
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String
-> CInt
-> (forall s. b -> MutableByteArray# s -> IO CInt)
-> a
-> Builder
CTB.convert String
"toShortest" CInt
len forall s. CFloat -> MutableByteArray# s -> IO CInt
c_Text_ToShortestFloat
        where len :: CInt
len = CInt
c_ToShortestLength
              {-# NOINLINE len #-}

    toPrecision :: Int -> Float -> T.Builder
    toPrecision :: Int -> Float -> Builder
toPrecision Int
ndigits = String
-> CInt
-> (forall s. CFloat -> MutableByteArray# s -> IO CInt)
-> Float
-> Builder
forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String
-> CInt
-> (forall s. b -> MutableByteArray# s -> IO CInt)
-> a
-> Builder
CTB.convert String
"toPrecision" CInt
len ((forall s. CFloat -> MutableByteArray# s -> IO CInt)
 -> Float -> Builder)
-> (forall s. CFloat -> MutableByteArray# s -> IO CInt)
-> Float
-> Builder
forall a b. (a -> b) -> a -> b
$ \CFloat
val MutableByteArray# s
mba ->
                          CFloat -> MutableByteArray# s -> CInt -> IO CInt
forall s. CFloat -> MutableByteArray# s -> CInt -> IO CInt
c_Text_ToPrecisionFloat CFloat
val MutableByteArray# s
mba (Int -> CInt
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
ndigits)
        where len :: CInt
len = CInt
c_ToPrecisionLength
              {-# NOINLINE len #-}