summaryrefslogtreecommitdiff
path: root/packages/base/src/Numeric/LinearAlgebra/Complex.hs
diff options
context:
space:
mode:
authorAlberto Ruiz <aruiz@um.es>2014-06-03 21:06:17 +0200
committerAlberto Ruiz <aruiz@um.es>2014-06-03 21:06:17 +0200
commit9a17969ad0ea9f940db6201a37b9aed19ad605df (patch)
treeccbf24f7fdcddc2d248b8deb0ca9b97a18fc94e4 /packages/base/src/Numeric/LinearAlgebra/Complex.hs
parent2734dd1ddc6b31aba6377ef969a33967babca519 (diff)
fix linspace, expose udot, complex static, wip
Diffstat (limited to 'packages/base/src/Numeric/LinearAlgebra/Complex.hs')
-rw-r--r--packages/base/src/Numeric/LinearAlgebra/Complex.hs80
1 files changed, 80 insertions, 0 deletions
diff --git a/packages/base/src/Numeric/LinearAlgebra/Complex.hs b/packages/base/src/Numeric/LinearAlgebra/Complex.hs
new file mode 100644
index 0000000..17bc397
--- /dev/null
+++ b/packages/base/src/Numeric/LinearAlgebra/Complex.hs
@@ -0,0 +1,80 @@
1{-# LANGUAGE DataKinds #-}
2{-# LANGUAGE KindSignatures #-}
3{-# LANGUAGE GeneralizedNewtypeDeriving #-}
4{-# LANGUAGE MultiParamTypeClasses #-}
5{-# LANGUAGE FunctionalDependencies #-}
6{-# LANGUAGE FlexibleContexts #-}
7{-# LANGUAGE ScopedTypeVariables #-}
8{-# LANGUAGE EmptyDataDecls #-}
9{-# LANGUAGE Rank2Types #-}
10{-# LANGUAGE FlexibleInstances #-}
11{-# LANGUAGE TypeOperators #-}
12{-# LANGUAGE ViewPatterns #-}
13{-# LANGUAGE GADTs #-}
14
15
16{- |
17Module : Numeric.LinearAlgebra.Complex
18Copyright : (c) Alberto Ruiz 2006-14
19License : BSD3
20Stability : experimental
21
22-}
23
24module Numeric.LinearAlgebra.Complex(
25 C,
26 vec2, vec3, vec4, (&), (#),
27 vect,
28 R
29) where
30
31import GHC.TypeLits
32import Numeric.HMatrix hiding (
33 (<>),(#>),(<·>),Konst(..),diag, disp,(¦),(——),row,col,vect,mat,linspace)
34import qualified Numeric.HMatrix as LA
35import Data.Proxy(Proxy)
36import Numeric.LinearAlgebra.Static
37
38
39
40instance forall n . KnownNat n => Show (C n)
41 where
42 show (ud1 -> v)
43 | size v == 1 = "("++show (v!0)++" :: C "++show d++")"
44 | otherwise = "(vect"++ drop 8 (show v)++" :: C "++show d++")"
45 where
46 d = fromIntegral . natVal $ (undefined :: Proxy n) :: Int
47
48
49ud1 :: C n -> Vector ℂ
50ud1 (C (Dim v)) = v
51
52mkC :: Vector ℂ -> C n
53mkC = C . Dim
54
55
56infixl 4 &
57(&) :: forall n . KnownNat n
58 => C n -> ℂ -> C (n+1)
59u & x = u # (mkC (LA.scalar x) :: C 1)
60
61infixl 4 #
62(#) :: forall n m . (KnownNat n, KnownNat m)
63 => C n -> C m -> C (n+m)
64(C u) # (C v) = C (vconcat u v)
65
66
67
68vec2 :: ℂ -> ℂ -> C 2
69vec2 a b = C (gvec2 a b)
70
71vec3 :: ℂ -> ℂ -> ℂ -> C 3
72vec3 a b c = C (gvec3 a b c)
73
74
75vec4 :: ℂ -> ℂ -> ℂ -> ℂ -> C 4
76vec4 a b c d = C (gvec4 a b c d)
77
78vect :: forall n . KnownNat n => [ℂ] -> C n
79vect xs = C (gvect "C" xs)
80