summaryrefslogtreecommitdiff
path: root/libraries/base/Data/Fixed.hs
diff options
context:
space:
mode:
Diffstat (limited to 'libraries/base/Data/Fixed.hs')
-rw-r--r--libraries/base/Data/Fixed.hs15
1 files changed, 10 insertions, 5 deletions
diff --git a/libraries/base/Data/Fixed.hs b/libraries/base/Data/Fixed.hs
index 232175a1ab..17e5141b33 100644
--- a/libraries/base/Data/Fixed.hs
+++ b/libraries/base/Data/Fixed.hs
@@ -1,7 +1,9 @@
-{-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE ScopedTypeVariables #-}
-{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE FlexibleInstances #-}
+{-# LANGUAGE PolyKinds #-}
+{-# LANGUAGE RankNTypes #-}
+{-# LANGUAGE ScopedTypeVariables #-}
+{-# LANGUAGE StandaloneKindSignatures #-}
+{-# LANGUAGE Trustworthy #-}
-----------------------------------------------------------------------------
-- |
@@ -41,6 +43,7 @@ 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
@@ -61,7 +64,8 @@ mod' n d = n - (fromInteger f) * d where
f = div' n d
-- | The type parameter should be an instance of 'HasResolution'.
-newtype Fixed (a :: k) = MkFixed Integer
+type Fixed :: forall k. k -> Type
+newtype Fixed a = MkFixed Integer
deriving ( Eq -- ^ @since 2.01
, Ord -- ^ @since 2.01
)
@@ -80,7 +84,8 @@ instance (Typeable k,Typeable a) => Data (Fixed (a :: k)) where
dataTypeOf _ = tyFixed
toConstr _ = conMkFixed
-class HasResolution (a :: k) where
+type HasResolution :: forall k. k -> Constraint
+class HasResolution a where
resolution :: p a -> Integer
-- | For example, @Fixed 1000@ will give you a 'Fixed' with a resolution of 1000.