summaryrefslogtreecommitdiff
path: root/libraries/base/Data/Fixed.hs
diff options
context:
space:
mode:
authorBen Gamari <ben@smart-cactus.org>2020-05-09 15:49:07 -0400
committerMarge Bot <ben+marge-bot@smart-cactus.org>2020-05-25 09:48:17 -0400
commit013d71204be44d660f01f8eb255db2d48b832421 (patch)
tree21ec9f79ef846bfa120471999b9fc47f7a6a9f17 /libraries/base/Data/Fixed.hs
parentcd339ef0e8ce940902df79ed1d93b3af50ea6f77 (diff)
downloadhaskell-013d71204be44d660f01f8eb255db2d48b832421.tar.gz
Revert "Specify kind variables for inferred kinds in base."
As noted in !3132, this has rather severe knock-on consequences in user-code. We'll need to revisit this before merging something along these lines. This reverts commit 9749fe1223d182b1f8e7e4f7378df661c509f396.
Diffstat (limited to 'libraries/base/Data/Fixed.hs')
-rw-r--r--libraries/base/Data/Fixed.hs15
1 files changed, 5 insertions, 10 deletions
diff --git a/libraries/base/Data/Fixed.hs b/libraries/base/Data/Fixed.hs
index 17e5141b33..232175a1ab 100644
--- a/libraries/base/Data/Fixed.hs
+++ b/libraries/base/Data/Fixed.hs
@@ -1,9 +1,7 @@
-{-# LANGUAGE FlexibleInstances #-}
-{-# LANGUAGE PolyKinds #-}
-{-# LANGUAGE RankNTypes #-}
-{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE StandaloneKindSignatures #-}
{-# LANGUAGE Trustworthy #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE FlexibleInstances #-}
-----------------------------------------------------------------------------
-- |
@@ -43,7 +41,6 @@ module Data.Fixed
import Data.Data
import GHC.TypeLits (KnownNat, natVal)
import GHC.Read
-import Data.Kind (Type, Constraint)
import Text.ParserCombinators.ReadPrec
import Text.Read.Lex
@@ -64,8 +61,7 @@ mod' n d = n - (fromInteger f) * d where
f = div' n d
-- | The type parameter should be an instance of 'HasResolution'.
-type Fixed :: forall k. k -> Type
-newtype Fixed a = MkFixed Integer
+newtype Fixed (a :: k) = MkFixed Integer
deriving ( Eq -- ^ @since 2.01
, Ord -- ^ @since 2.01
)
@@ -84,8 +80,7 @@ instance (Typeable k,Typeable a) => Data (Fixed (a :: k)) where
dataTypeOf _ = tyFixed
toConstr _ = conMkFixed
-type HasResolution :: forall k. k -> Constraint
-class HasResolution a where
+class HasResolution (a :: k) where
resolution :: p a -> Integer
-- | For example, @Fixed 1000@ will give you a 'Fixed' with a resolution of 1000.