File: Text.hs

package info (click to toggle)
haskell-double-conversion 2.0.5.0%2Bds1-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 152 kB
  • sloc: haskell: 611; cpp: 340; ansic: 31; makefile: 6
file content (58 lines) | stat: -rw-r--r-- 1,950 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
{-# 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 func len act val = runST go
  where
    go :: (forall s. ST s Text)
    go = do
      buf <- A.new (fromIntegral 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)