summaryrefslogtreecommitdiff
path: root/lib/Data
diff options
context:
space:
mode:
Diffstat (limited to 'lib/Data')
-rw-r--r--lib/Data/Packed.hs1
-rw-r--r--lib/Data/Packed/Matrix.hs181
-rw-r--r--lib/Data/Packed/Random.hs2
3 files changed, 30 insertions, 154 deletions
diff --git a/lib/Data/Packed.hs b/lib/Data/Packed.hs
index 50a5eb6..8128667 100644
--- a/lib/Data/Packed.hs
+++ b/lib/Data/Packed.hs
@@ -24,4 +24,3 @@ import Data.Packed.Vector
24import Data.Packed.Matrix 24import Data.Packed.Matrix
25import Data.Packed.Random 25import Data.Packed.Random
26import Data.Complex 26import Data.Complex
27import Numeric.LinearAlgebra.Instances()
diff --git a/lib/Data/Packed/Matrix.hs b/lib/Data/Packed/Matrix.hs
index 2855a90..07258f8 100644
--- a/lib/Data/Packed/Matrix.hs
+++ b/lib/Data/Packed/Matrix.hs
@@ -19,10 +19,7 @@
19----------------------------------------------------------------------------- 19-----------------------------------------------------------------------------
20 20
21module Data.Packed.Matrix ( 21module Data.Packed.Matrix (
22 Element, RealElement, Container(..), 22 Element(..),
23 Convert(..), RealOf, ComplexOf, SingleOf, DoubleOf, ElementOf,
24 Precision(..), comp,
25 AutoReal(..),
26 Matrix,rows,cols, 23 Matrix,rows,cols,
27 (><), 24 (><),
28 trans, 25 trans,
@@ -55,7 +52,7 @@ import Data.Complex
55import Data.Binary 52import Data.Binary
56import Foreign.Storable 53import Foreign.Storable
57import Control.Monad(replicateM) 54import Control.Monad(replicateM)
58import Control.Arrow((***)) 55--import Control.Arrow((***))
59--import GHC.Float(double2Float,float2Double) 56--import GHC.Float(double2Float,float2Double)
60 57
61------------------------------------------------------------------- 58-------------------------------------------------------------------
@@ -75,6 +72,33 @@ instance (Binary a, Element a, Storable a) => Binary (Matrix a) where
75 72
76------------------------------------------------------------------- 73-------------------------------------------------------------------
77 74
75instance (Show a, Element a) => (Show (Matrix a)) where
76 show m = (sizes++) . dsp . map (map show) . toLists $ m
77 where sizes = "("++show (rows m)++"><"++show (cols m)++")\n"
78
79dsp as = (++" ]") . (" ["++) . init . drop 2 . unlines . map (" , "++) . map unwords' $ transpose mtp
80 where
81 mt = transpose as
82 longs = map (maximum . map length) mt
83 mtp = zipWith (\a b -> map (pad a) b) longs mt
84 pad n str = replicate (n - length str) ' ' ++ str
85 unwords' = concat . intersperse ", "
86
87------------------------------------------------------------------
88
89instance (Element a, Read a) => Read (Matrix a) where
90 readsPrec _ s = [((rs><cs) . read $ listnums, rest)]
91 where (thing,rest) = breakAt ']' s
92 (dims,listnums) = breakAt ')' thing
93 cs = read . init . fst. breakAt ')' . snd . breakAt '<' $ dims
94 rs = read . snd . breakAt '(' .init . fst . breakAt '>' $ dims
95
96
97breakAt c l = (a++[c],tail b) where
98 (a,b) = break (==c) l
99
100------------------------------------------------------------------
101
78-- | creates a matrix from a vertical list of matrices 102-- | creates a matrix from a vertical list of matrices
79joinVert :: Element t => [Matrix t] -> Matrix t 103joinVert :: Element t => [Matrix t] -> Matrix t
80joinVert ms = case common cols ms of 104joinVert ms = case common cols ms of
@@ -470,150 +494,3 @@ toBlocksEvery r c m = toBlocks rs cs m where
470 cs = replicate qc c ++ if rc > 0 then [rc] else [] 494 cs = replicate qc c ++ if rc > 0 then [rc] else []
471 495
472------------------------------------------------------------------- 496-------------------------------------------------------------------
473
474-- | Supported single-double precision type pairs
475class (Element s, Element d) => Precision s d | s -> d, d -> s where
476 double2FloatG :: Vector d -> Vector s
477 float2DoubleG :: Vector s -> Vector d
478
479instance Precision Float Double where
480 double2FloatG = double2FloatV
481 float2DoubleG = float2DoubleV
482
483instance Precision (Complex Float) (Complex Double) where
484 double2FloatG = asComplex . double2FloatV . asReal
485 float2DoubleG = asComplex . float2DoubleV . asReal
486
487-- | Supported real types
488class (Element t, Element (Complex t), RealFloat t
489-- , RealOf t ~ t, RealOf (Complex t) ~ t
490 )
491 => RealElement t
492
493instance RealElement Double
494
495instance RealElement Float
496
497-- | Conversion utilities
498class Container c where
499 toComplex :: (RealElement e) => (c e, c e) -> c (Complex e)
500 fromComplex :: (RealElement e) => c (Complex e) -> (c e, c e)
501 complex' :: (RealElement e) => c e -> c (Complex e)
502 conj :: (RealElement e) => c (Complex e) -> c (Complex e)
503 cmap :: (Element a, Element b) => (a -> b) -> c a -> c b
504 single' :: Precision a b => c b -> c a
505 double' :: Precision a b => c a -> c b
506
507comp x = complex' x
508
509instance Container Vector where
510 toComplex = toComplexV
511 fromComplex = fromComplexV
512 complex' v = toComplex (v,constantD 0 (dim v))
513 conj = conjV
514 cmap = mapVector
515 single' = double2FloatG
516 double' = float2DoubleG
517
518instance Container Matrix where
519 toComplex = uncurry $ liftMatrix2 $ curry toComplex
520 fromComplex z = (reshape c *** reshape c) . fromComplex . flatten $ z
521 where c = cols z
522 complex' = liftMatrix complex'
523 conj = liftMatrix conj
524 cmap f = liftMatrix (cmap f)
525 single' = liftMatrix single'
526 double' = liftMatrix double'
527
528-------------------------------------------------------------------
529
530type family RealOf x
531
532type instance RealOf Double = Double
533type instance RealOf (Complex Double) = Double
534
535type instance RealOf Float = Float
536type instance RealOf (Complex Float) = Float
537
538type family ComplexOf x
539
540type instance ComplexOf Double = Complex Double
541type instance ComplexOf (Complex Double) = Complex Double
542
543type instance ComplexOf Float = Complex Float
544type instance ComplexOf (Complex Float) = Complex Float
545
546type family SingleOf x
547
548type instance SingleOf Double = Float
549type instance SingleOf Float = Float
550
551type instance SingleOf (Complex a) = Complex (SingleOf a)
552
553type family DoubleOf x
554
555type instance DoubleOf Double = Double
556type instance DoubleOf Float = Double
557
558type instance DoubleOf (Complex a) = Complex (DoubleOf a)
559
560type family ElementOf c
561
562type instance ElementOf (Vector a) = a
563type instance ElementOf (Matrix a) = a
564
565-------------------------------------------------------------------
566
567-- | generic conversion functions
568class Convert t where
569 real :: Container c => c (RealOf t) -> c t
570 complex :: Container c => c t -> c (ComplexOf t)
571 single :: Container c => c t -> c (SingleOf t)
572 double :: Container c => c t -> c (DoubleOf t)
573
574instance Convert Double where
575 real = id
576 complex = complex'
577 single = single'
578 double = id
579
580instance Convert Float where
581 real = id
582 complex = complex'
583 single = id
584 double = double'
585
586instance Convert (Complex Double) where
587 real = complex'
588 complex = id
589 single = single'
590 double = id
591
592instance Convert (Complex Float) where
593 real = complex'
594 complex = id
595 single = id
596 double = double'
597
598-------------------------------------------------------------------
599
600-- | to be replaced by Convert
601class Convert t => AutoReal t where
602 real'' :: Container c => c Double -> c t
603 complex'' :: Container c => c t -> c (Complex Double)
604
605instance AutoReal Double where
606 real'' = real
607 complex'' = complex
608
609instance AutoReal (Complex Double) where
610 real'' = real
611 complex'' = complex
612
613instance AutoReal Float where
614 real'' = real . single
615 complex'' = double . complex
616
617instance AutoReal (Complex Float) where
618 real'' = real . single
619 complex'' = double . complex
diff --git a/lib/Data/Packed/Random.hs b/lib/Data/Packed/Random.hs
index 33a11d7..579d13c 100644
--- a/lib/Data/Packed/Random.hs
+++ b/lib/Data/Packed/Random.hs
@@ -22,8 +22,8 @@ module Data.Packed.Random (
22import Numeric.GSL.Vector 22import Numeric.GSL.Vector
23import Data.Packed.Matrix 23import Data.Packed.Matrix
24import Data.Packed.Vector 24import Data.Packed.Vector
25import Numeric.LinearAlgebra.Algorithms
26import Numeric.LinearAlgebra.Linear 25import Numeric.LinearAlgebra.Linear
26import Numeric.LinearAlgebra.Algorithms
27 27
28-- | Obtains a matrix whose rows are pseudorandom samples from a multivariate 28-- | Obtains a matrix whose rows are pseudorandom samples from a multivariate
29-- Gaussian distribution. 29-- Gaussian distribution.