aboutsummaryrefslogtreecommitdiff
path: root/haddock-library/vendor/attoparsec-0.12.1.1/Data/Attoparsec/Number.hs
blob: 7438a912c276a03ef6c59d52921f380fdb7796d5 (plain) (blame)
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
{-# LANGUAGE DeriveDataTypeable #-}
-- |
-- Module      :  Data.Attoparsec.Number
-- Copyright   :  Bryan O'Sullivan 2007-2014
-- License     :  BSD3
--
-- Maintainer  :  bos@serpentine.com
-- Stability   :  experimental
-- Portability :  unknown
--
-- This module is deprecated, and both the module and 'Number' type
-- will be removed in the next major release.  Use the
-- <http://hackage.haskell.org/package/scientific scientific> package
-- and the 'Data.Scientific.Scientific' type instead.
--
-- A simple number type, useful for parsing both exact and inexact
-- quantities without losing much precision.
module Data.Attoparsec.Number
    {-# DEPRECATED "This module will be removed in the next major release." #-}
    (
      Number(..)
    ) where

import Control.DeepSeq (NFData(rnf))
import Data.Data (Data)
import Data.Function (on)
import Data.Typeable (Typeable)

-- | A numeric type that can represent integers accurately, and
-- floating point numbers to the precision of a 'Double'.
--
-- /Note/: this type is deprecated, and will be removed in the next
-- major release.  Use the 'Data.Scientific.Scientific' type instead.
data Number = I !Integer
            | D {-# UNPACK #-} !Double
              deriving (Typeable, Data)
{-# DEPRECATED Number "Use Scientific instead." #-}

instance Show Number where
    show (I a) = show a
    show (D a) = show a

instance NFData Number where
    rnf (I _) = ()
    rnf (D _) = ()
    {-# INLINE rnf #-}

binop :: (Integer -> Integer -> a) -> (Double -> Double -> a)
      -> Number -> Number -> a
binop _ d (D a) (D b) = d a b
binop i _ (I a) (I b) = i a b
binop _ d (D a) (I b) = d a (fromIntegral b)
binop _ d (I a) (D b) = d (fromIntegral a) b
{-# INLINE binop #-}

instance Eq Number where
    (==) = binop (==) (==)
    {-# INLINE (==) #-}

    (/=) = binop (/=) (/=)
    {-# INLINE (/=) #-}

instance Ord Number where
    (<) = binop (<) (<)
    {-# INLINE (<) #-}

    (<=) = binop (<=) (<=)
    {-# INLINE (<=) #-}

    (>) = binop (>) (>)
    {-# INLINE (>) #-}

    (>=) = binop (>=) (>=)
    {-# INLINE (>=) #-}

    compare = binop compare compare
    {-# INLINE compare #-}

instance Num Number where
    (+) = binop (((I$!).) . (+)) (((D$!).) . (+))
    {-# INLINE (+) #-}

    (-) = binop (((I$!).) . (-)) (((D$!).) . (-))
    {-# INLINE (-) #-}

    (*) = binop (((I$!).) . (*)) (((D$!).) . (*))
    {-# INLINE (*) #-}

    abs (I a) = I $! abs a
    abs (D a) = D $! abs a
    {-# INLINE abs #-}

    negate (I a) = I $! negate a
    negate (D a) = D $! negate a
    {-# INLINE negate #-}

    signum (I a) = I $! signum a
    signum (D a) = D $! signum a
    {-# INLINE signum #-}

    fromInteger = (I$!) . fromInteger
    {-# INLINE fromInteger #-}

instance Real Number where
    toRational (I a) = fromIntegral a
    toRational (D a) = toRational a
    {-# INLINE toRational #-}

instance Fractional Number where
    fromRational = (D$!) . fromRational
    {-# INLINE fromRational #-}

    (/) = binop (((D$!).) . (/) `on` fromIntegral)
                (((D$!).) . (/))
    {-# INLINE (/) #-}

    recip (I a) = D $! recip (fromIntegral a)
    recip (D a) = D $! recip a
    {-# INLINE recip #-}

instance RealFrac Number where
    properFraction (I a) = (fromIntegral a,0)
    properFraction (D a) = case properFraction a of
                             (i,d) -> (i,D d)
    {-# INLINE properFraction #-}
    truncate (I a) = fromIntegral a
    truncate (D a) = truncate a
    {-# INLINE truncate #-}
    round (I a) = fromIntegral a
    round (D a) = round a
    {-# INLINE round #-}
    ceiling (I a) = fromIntegral a
    ceiling (D a) = ceiling a
    {-# INLINE ceiling #-}
    floor (I a) = fromIntegral a
    floor (D a) = floor a
    {-# INLINE floor #-}