File: Convertable.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 (296 lines) | stat: -rw-r--r-- 12,310 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
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
{-# LANGUAGE DefaultSignatures, InstanceSigs, MagicHash, MultiParamTypeClasses,
             TypeFamilies, TypeOperators #-}

-- |
-- 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 can 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 via Builder (both in the in case of bytestring and text) in case of single number
-- is a bit slower, than to text or bytestring directly.
-- But conversion a large amount of numbers to text via Builder (for example using foldr) is much faster than direct conversion to Text (up to 10-15x).
--
-- The same works for bytestrings: conversion, for example, a list of 20000 doubles to bytestring builder 
-- and then to bytestring is about 13 times faster than direct conversion of this list to bytestring. 
--
-- Conversion to text via text builder is a little bit slower, than conversion to bytestring 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 ndigits num = primBounded (CBB.convert "toExponential" len $ \val mba ->
                        c_ToExponential val mba (fromIntegral ndigits)) (realToFrac num :: Double)
      where len = c_ToExponentialLength
            {-# NOINLINE len #-}

  toPrecision :: Int -> a -> b
  default toPrecision :: (b ~ BB.Builder) => Int -> a -> b
  toPrecision ndigits num = primBounded (CBB.convert "toPrecision" len $ \val mba ->
                      c_ToPrecision val mba (fromIntegral ndigits)) (realToFrac num :: Double)
      where len = c_ToPrecisionLength
            {-# NOINLINE len #-}

  toFixed :: Int -> a -> b
  default toFixed :: (b ~ BB.Builder) => Int -> a -> b
  toFixed ndigits num = primBounded (CBB.convert "toFixed" len $ \val mba ->
                  c_ToFixed val mba (fromIntegral ndigits)) (realToFrac num :: Double)
      where len = c_ToFixedLength
            {-# NOINLINE len #-}

  toShortest :: a -> b
  default toShortest :: (b ~ BB.Builder) => a -> b
  toShortest num = primBounded (CBB.convert "toShortest" len c_ToShortest) (realToFrac num :: Double)
      where len = c_ToShortestLength
            {-# NOINLINE len #-}

-- Instances

instance Convertable Double BB.Builder where
    toExponential :: Int -> Double -> BB.Builder
    toExponential ndigits = primBounded $ CBB.convert "toExponential" len $ \val mba ->
                        c_ToExponential val mba (fromIntegral ndigits)
        where len = c_ToExponentialLength
              {-# NOINLINE len #-}

    toPrecision :: Int -> Double -> BB.Builder
    toPrecision ndigits = primBounded (CBB.convert "toPrecision" len $ \val mba ->
                      c_ToPrecision val mba (fromIntegral ndigits))
        where len = c_ToPrecisionLength
              {-# NOINLINE len #-}

    toShortest :: Double -> BB.Builder
    toShortest = primBounded $ CBB.convert "toShortest" len c_ToShortest
        where len = c_ToShortestLength
              {-# NOINLINE len #-}

    toFixed :: Int -> Double -> BB.Builder
    toFixed ndigits = primBounded $ CBB.convert "toFixed" len $ \val mba ->
                  c_ToFixed val mba (fromIntegral ndigits)
        where len = c_ToFixedLength
              {-# NOINLINE len #-}


instance Convertable Float BB.Builder where
    toExponential :: Int -> Float -> BB.Builder
    toExponential ndigits = primBounded $ CBB.convert "toExponential" len $ \val mba ->
                        c_ToExponentialFloat val mba (fromIntegral ndigits)
        where len = c_ToExponentialLength
              {-# NOINLINE len #-}

    toPrecision :: Int -> Float -> BB.Builder
    toPrecision ndigits = primBounded (CBB.convert "toPrecision" len $ \val mba ->
                      c_ToPrecisionFloat val mba (fromIntegral ndigits))
        where len = c_ToPrecisionLength
              {-# NOINLINE len #-}

    toShortest :: Float -> BB.Builder
    toShortest = primBounded $ CBB.convert "toShortest" len c_ToShortestFloat
        where len = c_ToShortestLength
              {-# NOINLINE len #-}

    toFixed :: Int -> Float -> BB.Builder
    toFixed ndigits = primBounded $ CBB.convert "toFixed" len $ \val mba ->
                  c_ToFixedFloat val mba (fromIntegral ndigits)
        where len = 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 ndigits = CB.convert "toExponential" len $ \val mba ->
                        c_ToExponential val mba (fromIntegral ndigits)
        where len = c_ToExponentialLength
              {-# NOINLINE len #-}

    toFixed :: Int -> Double -> B.ByteString
    toFixed ndigits = CB.convert "toFixed" len $ \val mba ->
                  c_ToFixed val mba (fromIntegral ndigits)
        where len = c_ToFixedLength
              {-# NOINLINE len #-}

    toShortest :: Double -> B.ByteString
    toShortest = CB.convert "toShortest" len c_ToShortest
        where len = c_ToShortestLength
              {-# NOINLINE len #-}

    toPrecision :: Int -> Double -> B.ByteString
    toPrecision ndigits = CB.convert "toPrecision" len $ \val mba ->
                      c_ToPrecision val mba (fromIntegral ndigits)
        where len = c_ToPrecisionLength
              {-# NOINLINE len #-}


instance Convertable Float B.ByteString where
    toExponential :: Int -> Float -> B.ByteString
    toExponential ndigits = CB.convert "toExponential" len $ \val mba ->
                        c_ToExponentialFloat val mba (fromIntegral ndigits)
        where len = c_ToExponentialLength
              {-# NOINLINE len #-}

    toFixed :: Int -> Float -> B.ByteString
    toFixed ndigits = CB.convert "toFixed" len $ \val mba ->
                  c_ToFixedFloat val mba (fromIntegral ndigits)
        where len = c_ToFixedLength
              {-# NOINLINE len #-}

    toShortest :: Float -> B.ByteString
    toShortest = CB.convert "toShortest" len c_ToShortestFloat
        where len = c_ToShortestLength
              {-# NOINLINE len #-}

    toPrecision :: Int -> Float -> B.ByteString
    toPrecision ndigits = CB.convert "toPrecision" len $ \val mba ->
                      c_ToPrecisionFloat val mba (fromIntegral ndigits)
        where len = c_ToPrecisionLength
              {-# NOINLINE len #-}


instance Convertable Double Text where
    toExponential :: Int -> Double -> Text
    toExponential ndigits = CT.convert "toExponential" len $ \val mba ->
                            c_Text_ToExponential val mba (fromIntegral ndigits)
        where len = c_ToExponentialLength
              {-# NOINLINE len #-}

    toFixed :: Int -> Double -> Text
    toFixed ndigits = CT.convert "toFixed" len $ \val mba ->
                    c_Text_ToFixed val mba (fromIntegral ndigits)
        where len = c_ToFixedLength
              {-# NOINLINE len #-}

    toShortest :: Double -> Text
    toShortest = CT.convert "toShortest" len c_Text_ToShortest
        where len = c_ToShortestLength
              {-# NOINLINE len #-}

    toPrecision :: Int -> Double -> Text
    toPrecision ndigits = CT.convert "toPrecision" len $ \val mba ->
                          c_Text_ToPrecision val mba (fromIntegral ndigits)
        where len = c_ToPrecisionLength
              {-# NOINLINE len #-}


instance Convertable Float Text where
    toExponential :: Int -> Float -> Text
    toExponential ndigits = CT.convert "toExponential" len $ \val mba ->
                            c_Text_ToExponentialFloat val mba (fromIntegral ndigits)
        where len = c_ToExponentialLength
              {-# NOINLINE len #-}

    toFixed :: Int -> Float -> Text
    toFixed ndigits = CT.convert "toFixed" len $ \val mba ->
                    c_Text_ToFixedFloat val mba (fromIntegral ndigits)
        where len = c_ToFixedLength
              {-# NOINLINE len #-}

    toShortest :: Float -> Text
    toShortest = CT.convert "toShortest" len c_Text_ToShortestFloat
        where len = c_ToShortestLength
              {-# NOINLINE len #-}

    toPrecision :: Int -> Float -> Text
    toPrecision ndigits = CT.convert "toPrecision" len $ \val mba ->
                          c_Text_ToPrecisionFloat val mba (fromIntegral ndigits)
        where len = c_ToPrecisionLength
              {-# NOINLINE len #-}


instance Convertable Double T.Builder where
    toExponential :: Int -> Double -> T.Builder
    toExponential ndigits = CTB.convert "toExponential" len $ \val mba ->
                            c_Text_ToExponential val mba (fromIntegral ndigits)
        where len = c_ToExponentialLength
              {-# NOINLINE len #-}

    toFixed :: Int -> Double -> T.Builder
    toFixed ndigits = CTB.convert "toFixed" len $ \val mba ->
                      c_Text_ToFixed val mba (fromIntegral ndigits)
        where len = c_ToFixedLength
              {-# NOINLINE len #-}

    toShortest :: Double -> T.Builder
    toShortest = CTB.convert "toShortest" len c_Text_ToShortest
        where len = c_ToShortestLength
              {-# NOINLINE len #-}

    toPrecision :: Int -> Double -> T.Builder
    toPrecision ndigits = CTB.convert "toPrecision" len $ \val mba ->
                          c_Text_ToPrecision val mba (fromIntegral ndigits)
        where len = c_ToPrecisionLength
              {-# NOINLINE len #-}


instance Convertable Float T.Builder where
    toExponential :: Int -> Float -> T.Builder
    toExponential ndigits = CTB.convert "toExponential" len $ \val mba ->
                            c_Text_ToExponentialFloat val mba (fromIntegral ndigits)
        where len = c_ToExponentialLength
              {-# NOINLINE len #-}

    toFixed :: Int -> Float -> T.Builder
    toFixed ndigits = CTB.convert "toFixed" len $ \val mba ->
                      c_Text_ToFixedFloat val mba (fromIntegral ndigits)
        where len = c_ToFixedLength
              {-# NOINLINE len #-}

    toShortest :: Float -> T.Builder
    toShortest = CTB.convert "toShortest" len c_Text_ToShortestFloat
        where len = c_ToShortestLength
              {-# NOINLINE len #-}

    toPrecision :: Int -> Float -> T.Builder
    toPrecision ndigits = CTB.convert "toPrecision" len $ \val mba ->
                          c_Text_ToPrecisionFloat val mba (fromIntegral ndigits)
        where len = c_ToPrecisionLength
              {-# NOINLINE len #-}