summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--lib/Data/Packed/Matrix.hs114
-rw-r--r--lib/Numeric/LinearAlgebra/Algorithms.hs10
-rw-r--r--lib/Numeric/LinearAlgebra/Linear.hs9
-rw-r--r--lib/Numeric/LinearAlgebra/Tests/Instances.hs4
-rw-r--r--lib/Numeric/LinearAlgebra/Tests/Properties.hs5
-rw-r--r--packages/glpk/hmatrix-glpk.cabal4
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 @@
4{-# LANGUAGE MultiParamTypeClasses #-} 4{-# LANGUAGE MultiParamTypeClasses #-}
5{-# LANGUAGE FunctionalDependencies #-} 5{-# LANGUAGE FunctionalDependencies #-}
6 6
7
8----------------------------------------------------------------------------- 7-----------------------------------------------------------------------------
9-- | 8-- |
10-- Module : Data.Packed.Matrix 9-- Module : Data.Packed.Matrix
@@ -22,6 +21,7 @@
22module Data.Packed.Matrix ( 21module Data.Packed.Matrix (
23 Element, RealElement, Container(..), 22 Element, RealElement, Container(..),
24 Convert(..), RealOf, ComplexOf, SingleOf, DoubleOf, ElementOf, 23 Convert(..), RealOf, ComplexOf, SingleOf, DoubleOf, ElementOf,
24 Precision(..), comp, real'', complex'',
25 AutoReal(..), 25 AutoReal(..),
26 Matrix,rows,cols, 26 Matrix,rows,cols,
27 (><), 27 (><),
@@ -471,53 +471,54 @@ toBlocksEvery r c m = toBlocks rs cs m where
471 471
472------------------------------------------------------------------- 472-------------------------------------------------------------------
473 473
474-- | conversion utilities 474-- | Supported single-double precision type pairs
475 475class (Element s, Element d) => Precision s d | s -> d, d -> s where
476class (Element t, Element (Complex t), RealFloat t) => RealElement t
477
478instance RealElement Double
479instance RealElement Float
480
481class (Element s, Element d) => Prec s d | s -> d, d -> s where
482 double2FloatG :: Vector d -> Vector s 476 double2FloatG :: Vector d -> Vector s
483 float2DoubleG :: Vector s -> Vector d 477 float2DoubleG :: Vector s -> Vector d
484 478
485instance Prec Float Double where 479instance Precision Float Double where
486 double2FloatG = double2FloatV 480 double2FloatG = double2FloatV
487 float2DoubleG = float2DoubleV 481 float2DoubleG = float2DoubleV
488 482
489instance Prec (Complex Float) (Complex Double) where 483instance Precision (Complex Float) (Complex Double) where
490 double2FloatG = asComplex . double2FloatV . asReal 484 double2FloatG = asComplex . double2FloatV . asReal
491 float2DoubleG = asComplex . float2DoubleV . asReal 485 float2DoubleG = asComplex . float2DoubleV . asReal
492 486
487-- | Supported real types
488class (Element t, Element (Complex t), RealFloat t) => RealElement t
489
490instance RealElement Double
491
492instance RealElement Float
493 493
494-- | Conversion utilities
494class Container c where 495class Container c where
495 toComplex :: (RealElement e) => (c e, c e) -> c (Complex e) 496 toComplex :: (RealElement e) => (c e, c e) -> c (Complex e)
496 fromComplex :: (RealElement e) => c (Complex e) -> (c e, c e) 497 fromComplex :: (RealElement e) => c (Complex e) -> (c e, c e)
497 comp :: (RealElement e) => c e -> c (Complex e) 498 complex' :: (RealElement e) => c e -> c (Complex e)
498 conj :: (RealElement e) => c (Complex e) -> c (Complex e) 499 conj :: (RealElement e) => c (Complex e) -> c (Complex e)
499 cmap :: (Element a, Element b) => (a -> b) -> c a -> c b 500 cmap :: (Element a, Element b) => (a -> b) -> c a -> c b
500 single :: Prec a b => c b -> c a 501 single' :: Precision a b => c b -> c a
501 double :: Prec a b => c a -> c b 502 double' :: Precision a b => c a -> c b
502 503
503instance Container Vector where 504instance Container Vector where
504 toComplex = toComplexV 505 toComplex = toComplexV
505 fromComplex = fromComplexV 506 fromComplex = fromComplexV
506 comp v = toComplex (v,constantD 0 (dim v)) 507 complex' v = toComplex (v,constantD 0 (dim v))
507 conj = conjV 508 conj = conjV
508 cmap = mapVector 509 cmap = mapVector
509 single = double2FloatG 510 single' = double2FloatG
510 double = float2DoubleG 511 double' = float2DoubleG
511 512
512instance Container Matrix where 513instance Container Matrix where
513 toComplex = uncurry $ liftMatrix2 $ curry toComplex 514 toComplex = uncurry $ liftMatrix2 $ curry toComplex
514 fromComplex z = (reshape c *** reshape c) . fromComplex . flatten $ z 515 fromComplex z = (reshape c *** reshape c) . fromComplex . flatten $ z
515 where c = cols z 516 where c = cols z
516 comp = liftMatrix comp 517 complex' = liftMatrix complex'
517 conj = liftMatrix conj 518 conj = liftMatrix conj
518 cmap f = liftMatrix (cmap f) 519 cmap f = liftMatrix (cmap f)
519 single = liftMatrix single 520 single' = liftMatrix single'
520 double = liftMatrix double 521 double' = liftMatrix double'
521 522
522------------------------------------------------------------------- 523-------------------------------------------------------------------
523 524
@@ -560,54 +561,65 @@ type instance ElementOf (Matrix a) = a
560 561
561-- | generic conversion functions 562-- | generic conversion functions
562class Convert t where 563class Convert t where
563 real' :: Container c => c (RealOf t) -> c t 564 real :: Container c => c (RealOf t) -> c t
564 complex' :: Container c => c t -> c (ComplexOf t) 565 complex :: Container c => c t -> c (ComplexOf t)
565 single' :: Container c => c t -> c (SingleOf t) 566 single :: Container c => c t -> c (SingleOf t)
566 double' :: Container c => c t -> c (DoubleOf t) 567 double :: Container c => c t -> c (DoubleOf t)
567 568
568instance Convert Double where 569instance Convert Double where
569 real' = id 570 real = id
570 complex' = comp 571 complex = complex'
571 single' = single 572 single = single'
572 double' = id 573 double = id
573 574
574instance Convert Float where 575instance Convert Float where
575 real' = id 576 real = id
576 complex' = comp 577 complex = complex'
577 single' = id 578 single = id
578 double' = double 579 double = double'
579 580
580instance Convert (Complex Double) where 581instance Convert (Complex Double) where
581 real' = comp 582 real = complex'
582 complex' = id 583 complex = id
583 single' = single 584 single = single'
584 double' = id 585 double = id
585 586
586instance Convert (Complex Float) where 587instance Convert (Complex Float) where
587 real' = comp 588 real = complex'
588 complex' = id 589 complex = id
589 single' = id 590 single = id
590 double' = double 591 double = double'
591 592
592------------------------------------------------------------------- 593-------------------------------------------------------------------
593 594
595
594-- | to be replaced by Convert 596-- | to be replaced by Convert
595class AutoReal t where 597class Convert t => AutoReal t where
596 real :: Container c => c Double -> c t 598 real''' :: Container c => c Double -> c t
597 complex :: Container c => c t -> c (Complex Double) 599 complex''' :: Container c => c t -> c (Complex Double)
598 600
599instance AutoReal Double where 601instance AutoReal Double where
600 real = real' 602 real''' = real
601 complex = complex' 603 complex''' = complex
602 604
603instance AutoReal (Complex Double) where 605instance AutoReal (Complex Double) where
604 real = real' 606 real''' = real
605 complex = complex' 607 complex''' = complex
606 608
607instance AutoReal Float where 609instance AutoReal Float where
608 real = real' . single 610 real''' = real . single
609 complex = double . complex' 611 complex''' = double . complex
610 612
611instance AutoReal (Complex Float) where 613instance AutoReal (Complex Float) where
612 real = real' . single 614 real''' = real . single
613 complex = double . complex' 615 complex''' = double . complex
616
617
618comp x = complex' x
619
620-- complex'' x = double (complex x)
621-- real'' x = real (single x)
622
623real'' x = real''' x
624complex'' x = complex''' x
625
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')
82import Data.Array 82import Data.Array
83 83
84-- | Auxiliary typeclass used to define generic computations for both real and complex matrices. 84-- | Auxiliary typeclass used to define generic computations for both real and complex matrices.
85class (Prod t, Normed (Matrix t), Linear Vector t, Linear Matrix t) => Field t where 85class (AutoReal t, Prod t, Linear Vector t, Linear Matrix t) => Field t where
86 svd' :: Matrix t -> (Matrix t, Vector Double, Matrix t) 86 svd' :: Matrix t -> (Matrix t, Vector Double, Matrix t)
87 thinSVD' :: Matrix t -> (Matrix t, Vector Double, Matrix t) 87 thinSVD' :: Matrix t -> (Matrix t, Vector Double, Matrix t)
88 sv' :: Matrix t -> Vector Double 88 sv' :: Matrix t -> Vector Double
@@ -588,8 +588,8 @@ diagonalize m = if rank v == n
588-- 588--
589-- @logm = matFunc log@ 589-- @logm = matFunc log@
590-- 590--
591matFunc :: Field t => (Complex Double -> Complex Double) -> Matrix t -> Matrix (Complex Double) 591matFunc :: (Field t) => (Complex Double -> Complex Double) -> Matrix t -> Matrix (Complex Double)
592matFunc f m = case diagonalize (complex m) of 592matFunc f m = case diagonalize (complex'' m) of
593 Just (l,v) -> v `mXm` diag (mapVector f l) `mXm` inv v 593 Just (l,v) -> v `mXm` diag (mapVector f l) `mXm` inv v
594 Nothing -> error "Sorry, matFunc requires a diagonalizable matrix" 594 Nothing -> error "Sorry, matFunc requires a diagonalizable matrix"
595 595
@@ -630,7 +630,7 @@ expGolub m = iterate msq f !! j
630{- | Matrix exponential. It uses a direct translation of Algorithm 11.3.1 in Golub & Van Loan, 630{- | Matrix exponential. It uses a direct translation of Algorithm 11.3.1 in Golub & Van Loan,
631 based on a scaled Pade approximation. 631 based on a scaled Pade approximation.
632-} 632-}
633expm :: Field t => Matrix t -> Matrix t 633expm :: (Normed (Matrix t), Field t) => Matrix t -> Matrix t
634expm = expGolub 634expm = expGolub
635 635
636-------------------------------------------------------------- 636--------------------------------------------------------------
@@ -646,7 +646,7 @@ It only works with invertible matrices that have a real solution. For diagonaliz
646 [ 2.0, 2.25 646 [ 2.0, 2.25
647 , 0.0, 2.0 ]@ 647 , 0.0, 2.0 ]@
648-} 648-}
649sqrtm :: Field t => Matrix t -> Matrix t 649sqrtm :: (Normed (Matrix t), Field t) => Matrix t -> Matrix t
650sqrtm = sqrtmInv 650sqrtm = sqrtmInv
651 651
652sqrtmInv x = fst $ fixedPoint $ iterate f (x, ident (rows x)) 652sqrtmInv 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 (
21 Linear(..), 21 Linear(..),
22 -- * Products 22 -- * Products
23 Prod(..), 23 Prod(..),
24 mXm,mXv,vXm, mulH, 24 mXm,mXv,vXm,
25 outer, kronecker, 25 outer, kronecker,
26 -- * Creation of numeric vectors 26 -- * Creation of numeric vectors
27 constant, linspace 27 constant, linspace
@@ -90,7 +90,7 @@ instance Vectors Vector (Complex Double) where
90---------------------------------------------------- 90----------------------------------------------------
91 91
92-- | Basic element-by-element functions. 92-- | Basic element-by-element functions.
93class (Element e, AutoReal e, Container c) => Linear c e where 93class (Element e, Container c) => Linear c e where
94 -- | create a structure with a single element 94 -- | create a structure with a single element
95 scalar :: e -> c e 95 scalar :: e -> c e
96 scale :: e -> c e -> c e 96 scale :: e -> c e -> c e
@@ -190,13 +190,8 @@ linspace n (a,b) = addConstant a $ scale s $ fromList [0 .. fromIntegral n-1]
190 190
191---------------------------------------------------- 191----------------------------------------------------
192 192
193-- reference multiply
194mulH a b = fromLists [[ doth ai bj | bj <- toColumns b] | ai <- toRows a ]
195 where doth u v = sum $ zipWith (*) (toList u) (toList v)
196
197class Element t => Prod t where 193class Element t => Prod t where
198 multiply :: Matrix t -> Matrix t -> Matrix t 194 multiply :: Matrix t -> Matrix t -> Matrix t
199 multiply = mulH
200 ctrans :: Matrix t -> Matrix t 195 ctrans :: Matrix t -> Matrix t
201 196
202instance Prod Double where 197instance 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(
27) where 27) where
28 28
29 29
30import Numeric.LinearAlgebra 30import Numeric.LinearAlgebra hiding (real,complex)
31import Control.Monad(replicateM) 31import Control.Monad(replicateM)
32#include "quickCheckCompat.h" 32#include "quickCheckCompat.h"
33 33
34real x = real'' x
35complex x = complex'' x
34 36
35#if MIN_VERSION_QuickCheck(2,0,0) 37#if MIN_VERSION_QuickCheck(2,0,0)
36shrinkListElementwise :: (Arbitrary a) => [a] -> [[a]] 38shrinkListElementwise :: (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 (
42 linearSolveProp, linearSolveProp2 42 linearSolveProp, linearSolveProp2
43) where 43) where
44 44
45import Numeric.LinearAlgebra hiding (mulH) 45import Numeric.LinearAlgebra hiding (real,complex)
46import Numeric.LinearAlgebra.LAPACK 46import Numeric.LinearAlgebra.LAPACK
47import Debug.Trace 47import Debug.Trace
48#include "quickCheckCompat.h" 48#include "quickCheckCompat.h"
49 49
50 50
51real x = real'' x
52complex x = complex'' x
53
51debug x = trace (show x) x 54debug x = trace (show x) x
52 55
53-- relative error 56-- 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 @@
1Name: hmatrix-glpk 1Name: hmatrix-glpk
2Version: 0.2.0 2Version: 0.2.1
3License: GPL 3License: GPL
4License-file: LICENSE 4License-file: LICENSE
5Author: Alberto Ruiz 5Author: Alberto Ruiz
@@ -22,7 +22,7 @@ extra-source-files: examples/simplex1.hs
22 examples/simplex4.hs 22 examples/simplex4.hs
23 23
24library 24library
25 Build-Depends: base >= 3 && < 5, hmatrix >= 0.8.3 && < 0.10 25 Build-Depends: base >= 3 && < 5, hmatrix >= 0.8.3 && < 0.11
26 26
27 hs-source-dirs: lib 27 hs-source-dirs: lib
28 28