From c84049d82c9354bda7843c0b83f50c56f75b92e2 Mon Sep 17 00:00:00 2001 From: Alberto Ruiz Date: Tue, 9 Feb 2016 13:04:58 +0100 Subject: make ghc-8.0 happy --- packages/base/hmatrix.cabal | 2 +- packages/base/src/Internal/Matrix.hs | 3 +-- packages/base/src/Internal/Modular.hs | 16 ++++++++-------- packages/base/src/Internal/Static.hs | 18 +++++++++--------- 4 files changed, 19 insertions(+), 20 deletions(-) (limited to 'packages/base') diff --git a/packages/base/hmatrix.cabal b/packages/base/hmatrix.cabal index 5524d2b..aba6fa7 100644 --- a/packages/base/hmatrix.cabal +++ b/packages/base/hmatrix.cabal @@ -16,7 +16,7 @@ Description: Linear systems, matrix decompositions, and other numerical c Code examples: Category: Math -tested-with: GHC==7.10 +tested-with: GHC==8.0 cabal-version: >=1.8 diff --git a/packages/base/src/Internal/Matrix.hs b/packages/base/src/Internal/Matrix.hs index 3082e8d..6efbe5f 100644 --- a/packages/base/src/Internal/Matrix.hs +++ b/packages/base/src/Internal/Matrix.hs @@ -5,8 +5,7 @@ {-# LANGUAGE TypeOperators #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE ViewPatterns #-} - - +{-# LANGUAGE ConstrainedClassMethods #-} -- | -- Module : Internal.Matrix diff --git a/packages/base/src/Internal/Modular.hs b/packages/base/src/Internal/Modular.hs index 239c742..f3c59a8 100644 --- a/packages/base/src/Internal/Modular.hs +++ b/packages/base/src/Internal/Modular.hs @@ -72,7 +72,7 @@ instance (Ord t, KnownNat m) => Ord (Mod m t) where compare a b = compare (unMod a) (unMod b) -instance (Real t, KnownNat m, Integral (Mod m t)) => Real (Mod m t) +instance (Integral t, Real t, KnownNat m, Integral (Mod m t)) => Real (Mod m t) where toRational x = toInteger x % 1 @@ -114,7 +114,7 @@ instance Show t => Show (Mod n t) where show = show . unMod -instance forall n t . (Integral t, KnownNat n) => Num (Mod n t) +instance (Integral t, KnownNat n) => Num (Mod n t) where (+) = l2 (\m a b -> (a + b) `mod` (fromIntegral m)) (*) = l2 (\m a b -> (a * b) `mod` (fromIntegral m)) @@ -159,11 +159,11 @@ instance KnownNat m => Element (Mod m Z) m' = fromIntegral . natVal $ (undefined :: Proxy m) -instance forall m . KnownNat m => CTrans (Mod m I) -instance forall m . KnownNat m => CTrans (Mod m Z) +instance KnownNat m => CTrans (Mod m I) +instance KnownNat m => CTrans (Mod m Z) -instance forall m . KnownNat m => Container Vector (Mod m I) +instance KnownNat m => Container Vector (Mod m I) where conj' = id size' = dim @@ -203,7 +203,7 @@ instance forall m . KnownNat m => Container Vector (Mod m I) fromZ' = vmod . fromZ' toZ' = toZ' . f2i -instance forall m . KnownNat m => Container Vector (Mod m Z) +instance KnownNat m => Container Vector (Mod m Z) where conj' = id size' = dim @@ -311,7 +311,7 @@ lift2 f a b = vmod (f (f2i a) (f2i b)) lift2m f a b = liftMatrix vmod (f (f2iM a) (f2iM b)) -instance forall m . KnownNat m => Num (Vector (Mod m I)) +instance KnownNat m => Num (Vector (Mod m I)) where (+) = lift2 (+) (*) = lift2 (*) @@ -321,7 +321,7 @@ instance forall m . KnownNat m => Num (Vector (Mod m I)) negate = lift1 negate fromInteger x = fromInt (fromInteger x) -instance forall m . KnownNat m => Num (Vector (Mod m Z)) +instance KnownNat m => Num (Vector (Mod m Z)) where (+) = lift2 (+) (*) = lift2 (*) diff --git a/packages/base/src/Internal/Static.hs b/packages/base/src/Internal/Static.hs index 61be456..2c31097 100644 --- a/packages/base/src/Internal/Static.hs +++ b/packages/base/src/Internal/Static.hs @@ -191,7 +191,7 @@ singleV v = LA.size v == 1 singleM m = rows m == 1 && cols m == 1 -instance forall n. KnownNat n => Sized ℂ (C n) Vector +instance KnownNat n => Sized ℂ (C n) Vector where size _ = fromIntegral . natVal $ (undefined :: Proxy n) konst x = mkC (LA.scalar x) @@ -207,7 +207,7 @@ instance forall n. KnownNat n => Sized ℂ (C n) Vector r = mkC v :: C n -instance forall n. KnownNat n => Sized ℝ (R n) Vector +instance KnownNat n => Sized ℝ (R n) Vector where size _ = fromIntegral . natVal $ (undefined :: Proxy n) konst x = mkR (LA.scalar x) @@ -224,7 +224,7 @@ instance forall n. KnownNat n => Sized ℝ (R n) Vector -instance forall m n . (KnownNat m, KnownNat n) => Sized ℝ (L m n) Matrix +instance (KnownNat m, KnownNat n) => Sized ℝ (L m n) Matrix where size _ = ((fromIntegral . natVal) (undefined :: Proxy m) ,(fromIntegral . natVal) (undefined :: Proxy n)) @@ -242,7 +242,7 @@ instance forall m n . (KnownNat m, KnownNat n) => Sized ℝ (L m n) Matrix r = mkL x :: L m n -instance forall m n . (KnownNat m, KnownNat n) => Sized ℂ (M m n) Matrix +instance (KnownNat m, KnownNat n) => Sized ℂ (M m n) Matrix where size _ = ((fromIntegral . natVal) (undefined :: Proxy m) ,(fromIntegral . natVal) (undefined :: Proxy n)) @@ -300,7 +300,7 @@ isDiagg (Dim (Dim x)) -------------------------------------------------------------------------------- -instance forall n . KnownNat n => Show (R n) +instance KnownNat n => Show (R n) where show s@(R (Dim v)) | singleV v = "("++show (v!0)++" :: R "++show d++")" @@ -308,7 +308,7 @@ instance forall n . KnownNat n => Show (R n) where d = size s -instance forall n . KnownNat n => Show (C n) +instance KnownNat n => Show (C n) where show s@(C (Dim v)) | singleV v = "("++show (v!0)++" :: C "++show d++")" @@ -316,7 +316,7 @@ instance forall n . KnownNat n => Show (C n) where d = size s -instance forall m n . (KnownNat m, KnownNat n) => Show (L m n) +instance (KnownNat m, KnownNat n) => Show (L m n) where show (isDiag -> Just (z,y,(m',n'))) = printf "(diag %s %s :: L %d %d)" (show z) (drop 9 $ show y) m' n' show s@(L (Dim (Dim x))) @@ -325,7 +325,7 @@ instance forall m n . (KnownNat m, KnownNat n) => Show (L m n) where (m',n') = size s -instance forall m n . (KnownNat m, KnownNat n) => Show (M m n) +instance (KnownNat m, KnownNat n) => Show (M m n) where show (isDiagC -> Just (z,y,(m',n'))) = printf "(diag %s %s :: M %d %d)" (show z) (drop 9 $ show y) m' n' show s@(M (Dim (Dim x))) @@ -336,7 +336,7 @@ instance forall m n . (KnownNat m, KnownNat n) => Show (M m n) -------------------------------------------------------------------------------- -instance forall n t . (Num (Vector t), Numeric t )=> Num (Dim n (Vector t)) +instance (Num (Vector t), Numeric t )=> Num (Dim n (Vector t)) where (+) = lift2F (+) (*) = lift2F (*) -- cgit v1.2.3