summaryrefslogtreecommitdiff
path: root/lib/Data/Packed/Matrix.hs
diff options
context:
space:
mode:
Diffstat (limited to 'lib/Data/Packed/Matrix.hs')
-rw-r--r--lib/Data/Packed/Matrix.hs66
1 files changed, 46 insertions, 20 deletions
diff --git a/lib/Data/Packed/Matrix.hs b/lib/Data/Packed/Matrix.hs
index 8aa1693..8694249 100644
--- a/lib/Data/Packed/Matrix.hs
+++ b/lib/Data/Packed/Matrix.hs
@@ -1,6 +1,10 @@
1{-# LANGUAGE TypeFamilies #-} 1{-# LANGUAGE TypeFamilies #-}
2{-# LANGUAGE FlexibleContexts #-} 2{-# LANGUAGE FlexibleContexts #-}
3{-# LANGUAGE FlexibleInstances #-} 3{-# LANGUAGE FlexibleInstances #-}
4{-# LANGUAGE MultiParamTypeClasses #-}
5{-# LANGUAGE FunctionalDependencies #-}
6
7
4----------------------------------------------------------------------------- 8-----------------------------------------------------------------------------
5-- | 9-- |
6-- Module : Data.Packed.Matrix 10-- Module : Data.Packed.Matrix
@@ -16,8 +20,9 @@
16----------------------------------------------------------------------------- 20-----------------------------------------------------------------------------
17 21
18module Data.Packed.Matrix ( 22module Data.Packed.Matrix (
19 Element, Scalar, Container(..), Convert(..), 23 Element, RealElement, Container(..),
20 RealOf, ComplexOf, SingleOf, DoubleOf, ElementOf, AutoReal(..), 24 Convert(..), RealOf, ComplexOf, SingleOf, DoubleOf, ElementOf,
25 AutoReal(..),
21 Matrix,rows,cols, 26 Matrix,rows,cols,
22 (><), 27 (><),
23 trans, 28 trans,
@@ -51,7 +56,7 @@ import Data.Binary
51import Foreign.Storable 56import Foreign.Storable
52import Control.Monad(replicateM) 57import Control.Monad(replicateM)
53import Control.Arrow((***)) 58import Control.Arrow((***))
54import GHC.Float(double2Float,float2Double) 59--import GHC.Float(double2Float,float2Double)
55 60
56------------------------------------------------------------------- 61-------------------------------------------------------------------
57 62
@@ -468,17 +473,32 @@ toBlocksEvery r c m = toBlocks rs cs m where
468 473
469-- | conversion utilities 474-- | conversion utilities
470 475
471class (Element t, Element (Complex t), Fractional t, RealFloat t) => Scalar t 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
483 float2DoubleG :: Vector s -> Vector d
484
485instance Prec Float Double where
486 double2FloatG = double2FloatV
487 float2DoubleG = float2DoubleV
488
489instance Prec (Complex Float) (Complex Double) where
490 double2FloatG = asComplex . double2FloatV . asReal
491 float2DoubleG = asComplex . float2DoubleV . asReal
472 492
473instance Scalar Double
474instance Scalar Float
475 493
476class Container c where 494class Container c where
477 toComplex :: (Scalar e) => (c e, c e) -> c (Complex e) 495 toComplex :: (RealElement e) => (c e, c e) -> c (Complex e)
478 fromComplex :: (Scalar e) => c (Complex e) -> (c e, c e) 496 fromComplex :: (RealElement e) => c (Complex e) -> (c e, c e)
479 comp :: (Scalar e) => c e -> c (Complex e) 497 comp :: (RealElement e) => c e -> c (Complex e)
480 conj :: (Scalar e) => c (Complex e) -> c (Complex e) 498 conj :: (RealElement e) => c (Complex e) -> c (Complex e)
481 cmap :: (Element a, Element b) => (a -> b) -> c a -> c b 499 cmap :: (Element a, Element b) => (a -> b) -> c a -> c b
500 single :: Prec a b => c b -> c a
501 double :: Prec a b => c a -> c b
482 502
483instance Container Vector where 503instance Container Vector where
484 toComplex = toComplexV 504 toComplex = toComplexV
@@ -486,6 +506,8 @@ instance Container Vector where
486 comp v = toComplex (v,constantD 0 (dim v)) 506 comp v = toComplex (v,constantD 0 (dim v))
487 conj = conjV 507 conj = conjV
488 cmap = mapVector 508 cmap = mapVector
509 single = double2FloatG
510 double = float2DoubleG
489 511
490instance Container Matrix where 512instance Container Matrix where
491 toComplex = uncurry $ liftMatrix2 $ curry toComplex 513 toComplex = uncurry $ liftMatrix2 $ curry toComplex
@@ -494,6 +516,8 @@ instance Container Matrix where
494 comp = liftMatrix comp 516 comp = liftMatrix comp
495 conj = liftMatrix conj 517 conj = liftMatrix conj
496 cmap f = liftMatrix (cmap f) 518 cmap f = liftMatrix (cmap f)
519 single = liftMatrix single
520 double = liftMatrix double
497 521
498------------------------------------------------------------------- 522-------------------------------------------------------------------
499 523
@@ -534,38 +558,40 @@ type instance ElementOf (Matrix a) = a
534 558
535------------------------------------------------------------------- 559-------------------------------------------------------------------
536 560
561-- | generic conversion functions
537class Convert t where 562class Convert t where
538 real' :: Container c => c (RealOf t) -> c t 563 real' :: Container c => c (RealOf t) -> c t
539 complex' :: Container c => c t -> c (ComplexOf t) 564 complex' :: Container c => c t -> c (ComplexOf t)
540 single :: Container c => c t -> c (SingleOf t) 565 single' :: Container c => c t -> c (SingleOf t)
541 double :: Container c => c t -> c (DoubleOf t) 566 double' :: Container c => c t -> c (DoubleOf t)
542 567
543instance Convert Double where 568instance Convert Double where
544 real' = id 569 real' = id
545 complex' = comp 570 complex' = comp
546 single = cmap double2Float 571 single' = single
547 double = id 572 double' = id
548 573
549instance Convert Float where 574instance Convert Float where
550 real' = id 575 real' = id
551 complex' = comp 576 complex' = comp
552 single = id 577 single' = id
553 double = cmap float2Double 578 double' = double
554 579
555instance Convert (Complex Double) where 580instance Convert (Complex Double) where
556 real' = comp 581 real' = comp
557 complex' = id 582 complex' = id
558 single = toComplex . (single *** single) . fromComplex 583 single' = single
559 double = id 584 double' = id
560 585
561instance Convert (Complex Float) where 586instance Convert (Complex Float) where
562 real' = comp 587 real' = comp
563 complex' = id 588 complex' = id
564 single = id 589 single' = id
565 double = toComplex . (double *** double) . fromComplex 590 double' = double
566 591
567------------------------------------------------------------------- 592-------------------------------------------------------------------
568 593
594-- | to be replaced by Convert
569class AutoReal t where 595class AutoReal t where
570 real :: Container c => c Double -> c t 596 real :: Container c => c Double -> c t
571 complex :: Container c => c t -> c (Complex Double) 597 complex :: Container c => c t -> c (Complex Double)