[commit: ghc] master: Clean-up `Data.Fixed` (54addb1)
git at git.haskell.org
git at git.haskell.org
Fri Oct 31 13:33:12 UTC 2014
Repository : ssh://git@git.haskell.org/ghc
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/54addb12bfae03ac6567315c471981e4ee042693/ghc
>---------------------------------------------------------------
commit 54addb12bfae03ac6567315c471981e4ee042693
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date: Fri Oct 31 14:25:45 2014 +0100
Clean-up `Data.Fixed`
This gets rid of `-fno-warn-unused-binds` by turning the E* types into
constructor-less data types (as they're used as phantom-types only)
Moreover, this modules uses `AutoDeriveTypeable` so we can drop all those
redundant `deriving (Typeable)` lines as well
Reviewed By: austin, ekmett
Differential Revision: https://phabricator.haskell.org/D385
>---------------------------------------------------------------
54addb12bfae03ac6567315c471981e4ee042693
libraries/base/Data/Fixed.hs | 25 ++++++++-----------------
1 file changed, 8 insertions(+), 17 deletions(-)
diff --git a/libraries/base/Data/Fixed.hs b/libraries/base/Data/Fixed.hs
index b499617..068eec5 100644
--- a/libraries/base/Data/Fixed.hs
+++ b/libraries/base/Data/Fixed.hs
@@ -1,7 +1,6 @@
{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE AutoDeriveTypeable #-}
-{-# OPTIONS -Wall -fno-warn-unused-binds #-}
-----------------------------------------------------------------------------
-- |
@@ -37,7 +36,6 @@ module Data.Fixed
E12,Pico
) where
-import Data.Typeable
import Data.Data
import GHC.Read
import Text.ParserCombinators.ReadPrec
@@ -61,7 +59,7 @@ mod' n d = n - (fromInteger f) * d where
-- | The type parameter should be an instance of 'HasResolution'.
newtype Fixed a = MkFixed Integer -- ^ /Since: 4.7.0.0/
- deriving (Eq,Ord,Typeable)
+ deriving (Eq,Ord)
-- We do this because the automatically derived Data instance requires (Data a) context.
-- Our manual instance has the more general (Typeable a) context.
@@ -166,50 +164,43 @@ convertFixed (Number n)
e = ceiling (logBase 10 (fromInteger r) :: Double)
convertFixed _ = pfail
-data E0 = E0
- deriving (Typeable)
+data E0
instance HasResolution E0 where
resolution _ = 1
-- | resolution of 1, this works the same as Integer
type Uni = Fixed E0
-data E1 = E1
- deriving (Typeable)
+data E1
instance HasResolution E1 where
resolution _ = 10
-- | resolution of 10^-1 = .1
type Deci = Fixed E1
-data E2 = E2
- deriving (Typeable)
+data E2
instance HasResolution E2 where
resolution _ = 100
-- | resolution of 10^-2 = .01, useful for many monetary currencies
type Centi = Fixed E2
-data E3 = E3
- deriving (Typeable)
+data E3
instance HasResolution E3 where
resolution _ = 1000
-- | resolution of 10^-3 = .001
type Milli = Fixed E3
-data E6 = E6
- deriving (Typeable)
+data E6
instance HasResolution E6 where
resolution _ = 1000000
-- | resolution of 10^-6 = .000001
type Micro = Fixed E6
-data E9 = E9
- deriving (Typeable)
+data E9
instance HasResolution E9 where
resolution _ = 1000000000
-- | resolution of 10^-9 = .000000001
type Nano = Fixed E9
-data E12 = E12
- deriving (Typeable)
+data E12
instance HasResolution E12 where
resolution _ = 1000000000000
-- | resolution of 10^-12 = .000000000001
More information about the ghc-commits
mailing list