From ccff860bcd64a43a9144288a04d03e1366f80586 Mon Sep 17 00:00:00 2001 From: Alberto Ruiz Date: Sat, 28 Aug 2010 17:26:39 +0000 Subject: conversion function names --- lib/Data/Packed/Matrix.hs | 114 ++++++++++++++------------ lib/Numeric/LinearAlgebra/Algorithms.hs | 10 +-- lib/Numeric/LinearAlgebra/Linear.hs | 9 +- lib/Numeric/LinearAlgebra/Tests/Instances.hs | 4 +- lib/Numeric/LinearAlgebra/Tests/Properties.hs | 5 +- packages/glpk/hmatrix-glpk.cabal | 4 +- 6 files changed, 79 insertions(+), 67 deletions(-) diff --git a/lib/Data/Packed/Matrix.hs b/lib/Data/Packed/Matrix.hs index 8694249..9059723 100644 --- a/lib/Data/Packed/Matrix.hs +++ b/lib/Data/Packed/Matrix.hs @@ -4,7 +4,6 @@ {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE FunctionalDependencies #-} - ----------------------------------------------------------------------------- -- | -- Module : Data.Packed.Matrix @@ -22,6 +21,7 @@ module Data.Packed.Matrix ( Element, RealElement, Container(..), Convert(..), RealOf, ComplexOf, SingleOf, DoubleOf, ElementOf, + Precision(..), comp, real'', complex'', AutoReal(..), Matrix,rows,cols, (><), @@ -471,53 +471,54 @@ toBlocksEvery r c m = toBlocks rs cs m where ------------------------------------------------------------------- --- | conversion utilities - -class (Element t, Element (Complex t), RealFloat t) => RealElement t - -instance RealElement Double -instance RealElement Float - -class (Element s, Element d) => Prec s d | s -> d, d -> s where +-- | Supported single-double precision type pairs +class (Element s, Element d) => Precision s d | s -> d, d -> s where double2FloatG :: Vector d -> Vector s float2DoubleG :: Vector s -> Vector d -instance Prec Float Double where +instance Precision Float Double where double2FloatG = double2FloatV float2DoubleG = float2DoubleV -instance Prec (Complex Float) (Complex Double) where +instance Precision (Complex Float) (Complex Double) where double2FloatG = asComplex . double2FloatV . asReal float2DoubleG = asComplex . float2DoubleV . asReal +-- | Supported real types +class (Element t, Element (Complex t), RealFloat t) => RealElement t + +instance RealElement Double + +instance RealElement Float +-- | Conversion utilities class Container c where toComplex :: (RealElement e) => (c e, c e) -> c (Complex e) fromComplex :: (RealElement e) => c (Complex e) -> (c e, c e) - comp :: (RealElement e) => c e -> c (Complex e) + complex' :: (RealElement e) => c e -> c (Complex e) conj :: (RealElement e) => c (Complex e) -> c (Complex e) cmap :: (Element a, Element b) => (a -> b) -> c a -> c b - single :: Prec a b => c b -> c a - double :: Prec a b => c a -> c b + single' :: Precision a b => c b -> c a + double' :: Precision a b => c a -> c b instance Container Vector where toComplex = toComplexV fromComplex = fromComplexV - comp v = toComplex (v,constantD 0 (dim v)) + complex' v = toComplex (v,constantD 0 (dim v)) conj = conjV cmap = mapVector - single = double2FloatG - double = float2DoubleG + single' = double2FloatG + double' = float2DoubleG instance Container Matrix where toComplex = uncurry $ liftMatrix2 $ curry toComplex fromComplex z = (reshape c *** reshape c) . fromComplex . flatten $ z where c = cols z - comp = liftMatrix comp + complex' = liftMatrix complex' conj = liftMatrix conj cmap f = liftMatrix (cmap f) - single = liftMatrix single - double = liftMatrix double + single' = liftMatrix single' + double' = liftMatrix double' ------------------------------------------------------------------- @@ -560,54 +561,65 @@ type instance ElementOf (Matrix a) = a -- | generic conversion functions class Convert t where - real' :: Container c => c (RealOf t) -> c t - complex' :: Container c => c t -> c (ComplexOf t) - single' :: Container c => c t -> c (SingleOf t) - double' :: Container c => c t -> c (DoubleOf t) + real :: Container c => c (RealOf t) -> c t + complex :: Container c => c t -> c (ComplexOf t) + single :: Container c => c t -> c (SingleOf t) + double :: Container c => c t -> c (DoubleOf t) instance Convert Double where - real' = id - complex' = comp - single' = single - double' = id + real = id + complex = complex' + single = single' + double = id instance Convert Float where - real' = id - complex' = comp - single' = id - double' = double + real = id + complex = complex' + single = id + double = double' instance Convert (Complex Double) where - real' = comp - complex' = id - single' = single - double' = id + real = complex' + complex = id + single = single' + double = id instance Convert (Complex Float) where - real' = comp - complex' = id - single' = id - double' = double + real = complex' + complex = id + single = id + double = double' ------------------------------------------------------------------- + -- | to be replaced by Convert -class AutoReal t where - real :: Container c => c Double -> c t - complex :: Container c => c t -> c (Complex Double) +class Convert t => AutoReal t where + real''' :: Container c => c Double -> c t + complex''' :: Container c => c t -> c (Complex Double) instance AutoReal Double where - real = real' - complex = complex' + real''' = real + complex''' = complex instance AutoReal (Complex Double) where - real = real' - complex = complex' + real''' = real + complex''' = complex instance AutoReal Float where - real = real' . single - complex = double . complex' + real''' = real . single + complex''' = double . complex instance AutoReal (Complex Float) where - real = real' . single - complex = double . complex' + real''' = real . single + complex''' = double . complex + + +comp x = complex' x + +-- complex'' x = double (complex x) +-- real'' x = real (single x) + +real'' x = real''' x +complex'' x = complex''' x + diff --git a/lib/Numeric/LinearAlgebra/Algorithms.hs b/lib/Numeric/LinearAlgebra/Algorithms.hs index 8962c60..7e258de 100644 --- a/lib/Numeric/LinearAlgebra/Algorithms.hs +++ b/lib/Numeric/LinearAlgebra/Algorithms.hs @@ -82,7 +82,7 @@ import Data.List(foldl1') import Data.Array -- | Auxiliary typeclass used to define generic computations for both real and complex matrices. -class (Prod t, Normed (Matrix t), Linear Vector t, Linear Matrix t) => Field t where +class (AutoReal t, Prod t, Linear Vector t, Linear Matrix t) => Field t where svd' :: Matrix t -> (Matrix t, Vector Double, Matrix t) thinSVD' :: Matrix t -> (Matrix t, Vector Double, Matrix t) sv' :: Matrix t -> Vector Double @@ -588,8 +588,8 @@ diagonalize m = if rank v == n -- -- @logm = matFunc log@ -- -matFunc :: Field t => (Complex Double -> Complex Double) -> Matrix t -> Matrix (Complex Double) -matFunc f m = case diagonalize (complex m) of +matFunc :: (Field t) => (Complex Double -> Complex Double) -> Matrix t -> Matrix (Complex Double) +matFunc f m = case diagonalize (complex'' m) of Just (l,v) -> v `mXm` diag (mapVector f l) `mXm` inv v Nothing -> error "Sorry, matFunc requires a diagonalizable matrix" @@ -630,7 +630,7 @@ expGolub m = iterate msq f !! j {- | Matrix exponential. It uses a direct translation of Algorithm 11.3.1 in Golub & Van Loan, based on a scaled Pade approximation. -} -expm :: Field t => Matrix t -> Matrix t +expm :: (Normed (Matrix t), Field t) => Matrix t -> Matrix t expm = expGolub -------------------------------------------------------------- @@ -646,7 +646,7 @@ It only works with invertible matrices that have a real solution. For diagonaliz [ 2.0, 2.25 , 0.0, 2.0 ]@ -} -sqrtm :: Field t => Matrix t -> Matrix t +sqrtm :: (Normed (Matrix t), Field t) => Matrix t -> Matrix t sqrtm = sqrtmInv sqrtmInv x = fst $ fixedPoint $ iterate f (x, ident (rows x)) diff --git a/lib/Numeric/LinearAlgebra/Linear.hs b/lib/Numeric/LinearAlgebra/Linear.hs index 71869cb..67921d8 100644 --- a/lib/Numeric/LinearAlgebra/Linear.hs +++ b/lib/Numeric/LinearAlgebra/Linear.hs @@ -21,7 +21,7 @@ module Numeric.LinearAlgebra.Linear ( Linear(..), -- * Products Prod(..), - mXm,mXv,vXm, mulH, + mXm,mXv,vXm, outer, kronecker, -- * Creation of numeric vectors constant, linspace @@ -90,7 +90,7 @@ instance Vectors Vector (Complex Double) where ---------------------------------------------------- -- | Basic element-by-element functions. -class (Element e, AutoReal e, Container c) => Linear c e where +class (Element e, Container c) => Linear c e where -- | create a structure with a single element scalar :: e -> c e scale :: e -> c e -> c e @@ -190,13 +190,8 @@ linspace n (a,b) = addConstant a $ scale s $ fromList [0 .. fromIntegral n-1] ---------------------------------------------------- --- reference multiply -mulH a b = fromLists [[ doth ai bj | bj <- toColumns b] | ai <- toRows a ] - where doth u v = sum $ zipWith (*) (toList u) (toList v) - class Element t => Prod t where multiply :: Matrix t -> Matrix t -> Matrix t - multiply = mulH ctrans :: Matrix t -> Matrix t instance Prod Double where diff --git a/lib/Numeric/LinearAlgebra/Tests/Instances.hs b/lib/Numeric/LinearAlgebra/Tests/Instances.hs index ad59b25..aaaff28 100644 --- a/lib/Numeric/LinearAlgebra/Tests/Instances.hs +++ b/lib/Numeric/LinearAlgebra/Tests/Instances.hs @@ -27,10 +27,12 @@ module Numeric.LinearAlgebra.Tests.Instances( ) where -import Numeric.LinearAlgebra +import Numeric.LinearAlgebra hiding (real,complex) import Control.Monad(replicateM) #include "quickCheckCompat.h" +real x = real'' x +complex x = complex'' x #if MIN_VERSION_QuickCheck(2,0,0) shrinkListElementwise :: (Arbitrary a) => [a] -> [[a]] diff --git a/lib/Numeric/LinearAlgebra/Tests/Properties.hs b/lib/Numeric/LinearAlgebra/Tests/Properties.hs index f7a948e..9891d8a 100644 --- a/lib/Numeric/LinearAlgebra/Tests/Properties.hs +++ b/lib/Numeric/LinearAlgebra/Tests/Properties.hs @@ -42,12 +42,15 @@ module Numeric.LinearAlgebra.Tests.Properties ( linearSolveProp, linearSolveProp2 ) where -import Numeric.LinearAlgebra hiding (mulH) +import Numeric.LinearAlgebra hiding (real,complex) import Numeric.LinearAlgebra.LAPACK import Debug.Trace #include "quickCheckCompat.h" +real x = real'' x +complex x = complex'' x + debug x = trace (show x) x -- relative error diff --git a/packages/glpk/hmatrix-glpk.cabal b/packages/glpk/hmatrix-glpk.cabal index d251eca..d98d24d 100644 --- a/packages/glpk/hmatrix-glpk.cabal +++ b/packages/glpk/hmatrix-glpk.cabal @@ -1,5 +1,5 @@ Name: hmatrix-glpk -Version: 0.2.0 +Version: 0.2.1 License: GPL License-file: LICENSE Author: Alberto Ruiz @@ -22,7 +22,7 @@ extra-source-files: examples/simplex1.hs examples/simplex4.hs library - Build-Depends: base >= 3 && < 5, hmatrix >= 0.8.3 && < 0.10 + Build-Depends: base >= 3 && < 5, hmatrix >= 0.8.3 && < 0.11 hs-source-dirs: lib -- cgit v1.2.3