{-# LANGUAGE CPP, MagicHash, Rank2Types, TypeFamilies, BangPatterns, TypeOperators #-}

-- |
-- Module      : Data.Double.Conversion.Text
-- Copyright   : (c) 2011 MailRank, Inc.
--
-- License     : BSD-style
-- Maintainer  : bos@serpentine.com
-- Stability   : experimental
-- Portability : GHC
--
-- Fast, efficient support for converting between double precision
-- floating point values and text.
--
-- These functions are about 30 times faster than the default 'show'
-- implementation for the 'Double' type.

module Data.Double.Conversion.Internal.Text
    (
      convert
    ) where

import Control.Monad (when)
#if MIN_VERSION_base(4,4,0)
import Control.Monad.ST.Unsafe (unsafeIOToST)
#else
import Control.Monad.ST (unsafeIOToST)
#endif
import Control.Monad.ST (ST, runST)
import Data.Double.Conversion.Internal.FFI (ForeignFloating)
import qualified Data.Text.Array as A
import Data.Text.Internal (Text(Text))
import Foreign.C.Types (CDouble, CFloat, CInt)
import GHC.Prim (MutableByteArray#)


convert :: (RealFloat a, RealFloat b, b ~ ForeignFloating a) => String -> CInt
        -> (forall s. b -> MutableByteArray# s -> IO CInt)
        -> a -> Text
{-# SPECIALIZE convert :: String -> CInt -> (forall s. CDouble -> MutableByteArray# s -> IO CInt) -> Double -> Text #-}
{-# SPECIALIZE convert :: String -> CInt -> (forall s. CFloat -> MutableByteArray# s -> IO CInt) -> Float -> Text #-}
{-# INLINABLE convert #-}
convert :: forall a b.
(RealFloat a, RealFloat b, b ~ ForeignFloating a) =>
String
-> CInt
-> (forall s. b -> MutableByteArray# s -> IO CInt)
-> a
-> Text
convert String
func CInt
len forall s. b -> MutableByteArray# s -> IO CInt
act a
val = (forall s. ST s Text) -> Text
forall a. (forall s. ST s a) -> a
runST ST s Text
forall s. ST s Text
go
  where
    go :: (forall s. ST s Text)
    go :: forall s. ST s Text
go = do
      buf <- Int -> ST s (MArray s)
forall s. Int -> ST s (MArray s)
A.new (CInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegral CInt
len)
#if MIN_VERSION_text(2,0,0)
      let !(A.MutableByteArray ma) = buf
#else
      let ma = A.maBA buf
#endif
      size <- unsafeIOToST $ act (realToFrac val) ma
      when (size == -1) .
        error $ "Data.Double.Conversion.Text." ++ func ++
               ": conversion failed (invalid precision requested)"
      frozen <- A.unsafeFreeze buf
      return $ Text frozen 0 (fromIntegral size)