From b1b445697db31b1603a31747ca31151f97ee7263 Mon Sep 17 00:00:00 2001 From: Alberto Ruiz Date: Sat, 23 May 2015 12:31:32 +0200 Subject: join SContainer and Container using Fractional contexts --- packages/base/src/Data/Packed/Internal/Numeric.hs | 53 +++++++--------------- packages/base/src/Data/Packed/Numeric.hs | 13 +++--- packages/base/src/Numeric/Container.hs | 3 +- packages/base/src/Numeric/LinearAlgebra.hs | 2 +- .../src/Numeric/LinearAlgebra/Static/Internal.hs | 8 ++-- packages/base/src/Numeric/Matrix.hs | 4 +- packages/base/src/Numeric/Vector.hs | 2 +- 7 files changed, 33 insertions(+), 52 deletions(-) diff --git a/packages/base/src/Data/Packed/Internal/Numeric.hs b/packages/base/src/Data/Packed/Internal/Numeric.hs index 2e36de2..00ec70c 100644 --- a/packages/base/src/Data/Packed/Internal/Numeric.hs +++ b/packages/base/src/Data/Packed/Internal/Numeric.hs @@ -20,7 +20,7 @@ module Data.Packed.Internal.Numeric ( -- * Basic functions ident, diag, ctrans, -- * Generic operations - SContainer(..), Container(..), + Container(..), scalar, conj, scale, arctan2, cmap, atIndex, minIndex, maxIndex, minElement, maxElement, sumElements, prodElements, @@ -115,7 +115,7 @@ m ¿¿ ec = trans (trans m ?? ec) -- | Basic element-by-element functions for numeric containers -class Element e => SContainer c e +class Element e => Container c e where conj' :: c e -> c e size' :: c e -> IndexOf c @@ -155,24 +155,20 @@ class Element e => SContainer c e -> [(IndexOf c, e)] -- ^ association list -> c e -- ^ result - --- | Basic element-by-element functions for numeric containers -class (Fractional e, SContainer c e) => Container c e - where -- | scale the element by element reciprocal of the object: -- -- @scaleRecip 2 (fromList [5,i]) == 2 |> [0.4 :+ 0.0,0.0 :+ (-2.0)]@ - scaleRecip :: e -> c e -> c e + scaleRecip :: Fractional e => e -> c e -> c e -- | element by element division - divide :: c e -> c e -> c e + divide :: Fractional e => c e -> c e -> c e -- -- element by element inverse tangent - arctan2' :: c e -> c e -> c e + arctan2' :: Fractional e => c e -> c e -> c e -------------------------------------------------------------------------- -instance SContainer Vector CInt +instance Container Vector CInt where conj' = id size' = dim @@ -198,9 +194,11 @@ instance SContainer Vector CInt assoc' = assocV accum' = accumV -- cond' = condV condI + scaleRecip = undefined -- cannot match + divide = undefined + arctan2' = undefined - -instance SContainer Vector Float +instance Container Vector Float where conj' = id size' = dim @@ -226,16 +224,13 @@ instance SContainer Vector Float assoc' = assocV accum' = accumV cond' = condV condF - -instance Container Vector Float - where scaleRecip = vectorMapValF Recip divide = vectorZipF Div arctan2' = vectorZipF ATan2 -instance SContainer Vector Double +instance Container Vector Double where conj' = id size' = dim @@ -261,15 +256,12 @@ instance SContainer Vector Double assoc' = assocV accum' = accumV cond' = condV condD - -instance Container Vector Double - where scaleRecip = vectorMapValR Recip divide = vectorZipR Div arctan2' = vectorZipR ATan2 -instance SContainer Vector (Complex Double) +instance Container Vector (Complex Double) where conj' = conjugateC size' = dim @@ -295,15 +287,11 @@ instance SContainer Vector (Complex Double) assoc' = assocV accum' = accumV cond' = undefined -- cannot match - - -instance Container Vector (Complex Double) - where scaleRecip = vectorMapValC Recip divide = vectorZipC Div arctan2' = vectorZipC ATan2 -instance SContainer Vector (Complex Float) +instance Container Vector (Complex Float) where conj' = conjugateQ size' = dim @@ -329,16 +317,13 @@ instance SContainer Vector (Complex Float) assoc' = assocV accum' = accumV cond' = undefined -- cannot match - -instance Container Vector (Complex Float) - where scaleRecip = vectorMapValQ Recip divide = vectorZipQ Div arctan2' = vectorZipQ ATan2 --------------------------------------------------------------- -instance (Num a, Element a, SContainer Vector a) => SContainer Matrix a +instance (Num a, Element a, Container Vector a) => Container Matrix a where conj' = liftMatrix conj' size' = size @@ -366,10 +351,6 @@ instance (Num a, Element a, SContainer Vector a) => SContainer Matrix a assoc' = assocM accum' = accumM cond' = condM - - -instance (Fractional a, Container Vector a) => Container Matrix a - where scaleRecip x = liftMatrix (scaleRecip x) divide = liftMatrix2 divide arctan2' = liftMatrix2 arctan2' @@ -404,7 +385,7 @@ conj = conj' scale :: Container c e => e -> c e -> c e scale = scale' -arctan2 :: Container c e => c e -> c e -> c e +arctan2 :: (Fractional e, Container c e) => c e -> c e -> c e arctan2 = arctan2' -- | like 'fmap' (cannot implement instance Functor because of Element class constraint) @@ -754,7 +735,7 @@ buildV n f = fromList [f k | k <- ks] -------------------------------------------------------- -- | conjugate transpose -ctrans :: (SContainer Vector e, Element e) => Matrix e -> Matrix e +ctrans :: (Container Vector e, Element e) => Matrix e -> Matrix e ctrans = liftMatrix conj' . trans -- | Creates a square matrix with a given diagonal. @@ -810,7 +791,7 @@ class Transposable m mt | m -> mt, mt -> m -- | (conjugate) transpose tr :: m -> mt -instance (SContainer Vector t) => Transposable (Matrix t) (Matrix t) +instance (Container Vector t) => Transposable (Matrix t) (Matrix t) where tr = ctrans diff --git a/packages/base/src/Data/Packed/Numeric.hs b/packages/base/src/Data/Packed/Numeric.hs index 4d66f27..d11ecf9 100644 --- a/packages/base/src/Data/Packed/Numeric.hs +++ b/packages/base/src/Data/Packed/Numeric.hs @@ -31,7 +31,7 @@ module Data.Packed.Numeric ( diag, ident, ctrans, -- * Generic operations - SContainer(..), Container(..), Numeric, + Container(..), Numeric, -- add, mul, sub, divide, equal, scaleRecip, addConstant, scalar, conj, scale, arctan2, cmap, atIndex, minIndex, maxIndex, minElement, maxElement, @@ -88,7 +88,7 @@ Logarithmic spacing can be defined as follows: @logspace n (a,b) = 10 ** linspace n (a,b)@ -} -linspace :: (Container Vector e) => Int -> (e, e) -> Vector e +linspace :: (Fractional e, Container Vector e) => Int -> (e, e) -> Vector e linspace 0 _ = fromList[] linspace 1 (a,b) = fromList[(a+b)/2] linspace n (a,b) = addConstant a $ scale s $ fromList $ map fromIntegral [0 .. n-1] @@ -219,11 +219,11 @@ class Konst e d c | d -> c, c -> d -- konst :: e -> d -> c e -instance SContainer Vector e => Konst e Int Vector +instance Container Vector e => Konst e Int Vector where konst = konst' -instance (Num e, SContainer Vector e) => Konst e (Int,Int) Matrix +instance (Num e, Container Vector e) => Konst e (Int,Int) Matrix where konst = konst' @@ -246,11 +246,11 @@ class Build d f c e | d -> c, c -> d, f -> e, f -> d, f -> c, c e -> f, d e -> f -- build :: d -> f -> c e -instance SContainer Vector e => Build Int (e -> e) Vector e +instance Container Vector e => Build Int (e -> e) Vector e where build = build' -instance SContainer Matrix e => Build (Int,Int) (e -> e -> e) Matrix e +instance Container Matrix e => Build (Int,Int) (e -> e -> e) Matrix e where build = build' @@ -299,5 +299,6 @@ instance Numeric Double instance Numeric (Complex Double) instance Numeric Float instance Numeric (Complex Float) +instance Numeric CInt diff --git a/packages/base/src/Numeric/Container.hs b/packages/base/src/Numeric/Container.hs index 5c1a28b..48291a1 100644 --- a/packages/base/src/Numeric/Container.hs +++ b/packages/base/src/Numeric/Container.hs @@ -7,8 +7,7 @@ module Numeric.Container( diag, ident, ctrans, - SContainer(addConstant,add, sub, mul, equal), - Container(scaleRecip,divide), + Container(addConstant,add, sub, mul, equal,scaleRecip,divide), scalar, conj, scale, diff --git a/packages/base/src/Numeric/LinearAlgebra.hs b/packages/base/src/Numeric/LinearAlgebra.hs index 246c728..4ba0c98 100644 --- a/packages/base/src/Numeric/LinearAlgebra.hs +++ b/packages/base/src/Numeric/LinearAlgebra.hs @@ -137,7 +137,7 @@ module Numeric.LinearAlgebra ( meanCov, rowOuters, pairwiseD2, unitary, peps, relativeError, haussholder, optimiseMult, udot, nullspaceSVD, orthSVD, ranksv, ℝ,ℂ,iC, -- * Auxiliary classes - Element, SContainer, Container, Product, Numeric, LSDiv, + Element, Container, Product, Numeric, LSDiv, Complexable, RealElement, RealOf, ComplexOf, SingleOf, DoubleOf, IndexOf, diff --git a/packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs b/packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs index a5fc29b..7ecb132 100644 --- a/packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs +++ b/packages/base/src/Numeric/LinearAlgebra/Static/Internal.hs @@ -322,12 +322,12 @@ instance forall n t . (Num (Vector t), Numeric t )=> Num (Dim n (Vector t)) negate = lift1F negate fromInteger x = Dim (fromInteger x) -instance (Num (Vector t), Num (Matrix t), Numeric t) => Fractional (Dim n (Vector t)) +instance (Num (Vector t), Num (Matrix t), Fractional t, Numeric t) => Fractional (Dim n (Vector t)) where fromRational x = Dim (fromRational x) (/) = lift2F (/) -instance (Floating (Vector t), Numeric t) => Floating (Dim n (Vector t)) where +instance (Fractional t, Floating (Vector t), Numeric t) => Floating (Dim n (Vector t)) where sin = lift1F sin cos = lift1F cos tan = lift1F tan @@ -357,12 +357,12 @@ instance (Num (Matrix t), Numeric t) => Num (Dim m (Dim n (Matrix t))) negate = (lift1F . lift1F) negate fromInteger x = Dim (Dim (fromInteger x)) -instance (Num (Vector t), Num (Matrix t), Numeric t) => Fractional (Dim m (Dim n (Matrix t))) +instance (Num (Vector t), Num (Matrix t), Fractional t, Numeric t) => Fractional (Dim m (Dim n (Matrix t))) where fromRational x = Dim (Dim (fromRational x)) (/) = (lift2F.lift2F) (/) -instance (Num (Vector t), Floating (Matrix t), Numeric t) => Floating (Dim m (Dim n (Matrix t))) where +instance (Num (Vector t), Floating (Matrix t), Fractional t, Numeric t) => Floating (Dim m (Dim n (Matrix t))) where sin = (lift1F . lift1F) sin cos = (lift1F . lift1F) cos tan = (lift1F . lift1F) tan diff --git a/packages/base/src/Numeric/Matrix.hs b/packages/base/src/Numeric/Matrix.hs index a9022c6..5f27652 100644 --- a/packages/base/src/Numeric/Matrix.hs +++ b/packages/base/src/Numeric/Matrix.hs @@ -37,7 +37,7 @@ import Numeric.Chain instance Container Matrix a => Eq (Matrix a) where (==) = equal -instance (Container Matrix a, Num (Vector a)) => Num (Matrix a) where +instance (Container Matrix a, Num a, Num (Vector a)) => Num (Matrix a) where (+) = liftMatrix2Auto (+) (-) = liftMatrix2Auto (-) negate = liftMatrix negate @@ -48,7 +48,7 @@ instance (Container Matrix a, Num (Vector a)) => Num (Matrix a) where --------------------------------------------------- -instance (Container Vector a, Fractional (Vector a), Num (Matrix a)) => Fractional (Matrix a) where +instance (Container Vector a, Fractional a, Fractional (Vector a), Num (Matrix a)) => Fractional (Matrix a) where fromRational n = (1><1) [fromRational n] (/) = liftMatrix2Auto (/) diff --git a/packages/base/src/Numeric/Vector.hs b/packages/base/src/Numeric/Vector.hs index 28b453f..1c16871 100644 --- a/packages/base/src/Numeric/Vector.hs +++ b/packages/base/src/Numeric/Vector.hs @@ -66,7 +66,7 @@ instance Num (Vector (Complex Float)) where --------------------------------------------------- -instance (Container Vector a, Num (Vector a)) => Fractional (Vector a) where +instance (Container Vector a, Num (Vector a), Fractional a) => Fractional (Vector a) where fromRational n = fromList [fromRational n] (/) = adaptScalar f divide g where r `f` v = scaleRecip r v -- cgit v1.2.3