aboutsummaryrefslogtreecommitdiff
path: root/haddock-library/vendor/attoparsec-0.12.1.1/Data/Attoparsec/Number.hs
diff options
context:
space:
mode:
authorMateusz Kowalczyk <fuuzetsu@fuuzetsu.co.uk>2014-08-08 01:41:34 +0200
committerMateusz Kowalczyk <fuuzetsu@fuuzetsu.co.uk>2014-08-08 04:58:19 +0200
commitd8f1c1cc4e8825f39ffc87fddfe6ff9c58f9ef8e (patch)
treefee259c5f50174842c5c843ab89a8f88250547f4 /haddock-library/vendor/attoparsec-0.12.1.1/Data/Attoparsec/Number.hs
parentd9b224f124edc99f051dfc0dcab922041654c36a (diff)
Update to attoparsec-0.12.1.1
There seems to be memory and speed improvement.
Diffstat (limited to 'haddock-library/vendor/attoparsec-0.12.1.1/Data/Attoparsec/Number.hs')
-rw-r--r--haddock-library/vendor/attoparsec-0.12.1.1/Data/Attoparsec/Number.hs137
1 files changed, 137 insertions, 0 deletions
diff --git a/haddock-library/vendor/attoparsec-0.12.1.1/Data/Attoparsec/Number.hs b/haddock-library/vendor/attoparsec-0.12.1.1/Data/Attoparsec/Number.hs
new file mode 100644
index 00000000..7438a912
--- /dev/null
+++ b/haddock-library/vendor/attoparsec-0.12.1.1/Data/Attoparsec/Number.hs
@@ -0,0 +1,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 #-}