Skip to content

Commit

Permalink
Merge pull request #270 from pdobsan/master
Browse files Browse the repository at this point in the history
Fixed vector show instance and related haddock entries.
  • Loading branch information
idontgetoutmuch committed May 20, 2018
2 parents 41638b9 + 39a7020 commit 2df7362
Show file tree
Hide file tree
Showing 11 changed files with 59 additions and 38 deletions.
2 changes: 1 addition & 1 deletion packages/base/hmatrix.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -47,7 +47,7 @@ library
bytestring,
storable-complex,
semigroups,
vector >= 0.8
vector >= 0.11

hs-source-dirs: src

Expand Down
11 changes: 7 additions & 4 deletions packages/base/src/Internal/Algorithms.hs
Original file line number Diff line number Diff line change
Expand Up @@ -170,7 +170,8 @@ a = (5><3)
-0.690 -0.352 0.433 -0.233 0.398
>>> s
fromList [35.18264833189422,1.4769076999800903,1.089145439970417e-15]
[35.18264833189422,1.4769076999800903,1.089145439970417e-15]
it :: Vector Double
>>> disp 3 v
3x3
Expand Down Expand Up @@ -224,7 +225,8 @@ a = (5><3)
-0.690 -0.352 0.433
>>> s
fromList [35.18264833189422,1.4769076999800903,1.089145439970417e-15]
[35.18264833189422,1.4769076999800903,1.089145439970417e-15]
it :: Vector Double
>>> disp 3 v
3x3
Expand Down Expand Up @@ -283,7 +285,8 @@ a = (5><3)
-0.690 -0.352
>>> s
fromList [35.18264833189422,1.4769076999800903]
[35.18264833189422,1.476907699980091]
it :: Vector Double
>>> disp 3 u
5x2
Expand Down Expand Up @@ -535,7 +538,7 @@ a = (3><3)
>>> let (l, v) = eigSH a
>>> l
fromList [11.344814282762075,0.17091518882717918,-0.5157294715892575]
[11.344814282762075,0.17091518882717918,-0.5157294715892575]
>>> disp 3 $ v <> diag l <> tr v
3x3
Expand Down
31 changes: 18 additions & 13 deletions packages/base/src/Internal/Container.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,10 +40,12 @@ import Prelude hiding ((<>))
{- | Creates a real vector containing a range of values:
>>> linspace 5 (-3,7::Double)
fromList [-3.0,-0.5,2.0,4.5,7.0]@
[-3.0,-0.5,2.0,4.5,7.0]
it :: Vector Double
>>> linspace 5 (8,2+i) :: Vector (Complex Double)
fromList [8.0 :+ 0.0,6.5 :+ 0.25,5.0 :+ 0.5,3.5 :+ 0.75,2.0 :+ 1.0]
>>> linspace 5 (8,3:+2) :: Vector (Complex Double)
[8.0 :+ 0.0,6.75 :+ 0.5,5.5 :+ 1.0,4.25 :+ 1.5,3.0 :+ 2.0]
it :: Vector (Complex Double)
Logarithmic spacing can be defined as follows:
Expand Down Expand Up @@ -87,7 +89,8 @@ infixr 8 <.>
>>> let v = vector [10,20,30]
>>> m #> v
fromList [140.0,320.0]
[140.0,320.0]
it :: Vector Numeric.LinearAlgebra.Data.R
-}
infixr 8 #>
Expand Down Expand Up @@ -136,10 +139,12 @@ v = vector [13.0,27.0,1.0]
>>> let x = a <\> v
>>> x
fromList [3.0799999999999996,5.159999999999999]
[3.0799999999999996,5.159999999999999]
it :: Vector Numeric.LinearAlgebra.Data.R
>>> a #> x
fromList [13.399999999999999,26.799999999999997,1.0]
[13.399999999999999,26.799999999999997,0.9999999999999991]
it :: Vector Numeric.LinearAlgebra.Data.R
It also admits multiple right-hand sides stored as columns in a matrix.
Expand Down Expand Up @@ -167,7 +172,8 @@ class Build d f c e | d -> c, c -> d, f -> e, f -> d, f -> c, c e -> f, d e -> f
where
-- |
-- >>> build 5 (**2) :: Vector Double
-- fromList [0.0,1.0,4.0,9.0,16.0]
-- [0.0,1.0,4.0,9.0,16.0]
-- it :: Vector Double
--
-- Hilbert matrix of order N:
--
Expand Down Expand Up @@ -204,12 +210,11 @@ optimiseMult = mconcat

{- | Compute mean vector and covariance matrix of the rows of a matrix.
>>> meanCov $ gaussianSample 666 1000 (fromList[4,5]) (diagl[2,3])
(fromList [4.010341078059521,5.0197204699640405],
(2><2)
[ 1.9862461923890056, -1.0127225830525157e-2
, -1.0127225830525157e-2, 3.0373954915729318 ])
>>> meanCov $ gaussianSample 666 1000 (fromList[4,5]) (trustSym $ diagl [2,3])
([3.9933155655086696,5.061409102770331],Herm (2><2)
[ 1.9963242906624408, -4.227815571404954e-2
, -4.227815571404954e-2, 3.2003833097832857 ])
it :: (Vector Double, Herm Double)
-}
meanCov :: Matrix Double -> (Vector Double, Herm Double)
meanCov x = (med,cov) where
Expand Down
6 changes: 4 additions & 2 deletions packages/base/src/Internal/Convolution.hs
Original file line number Diff line number Diff line change
Expand Up @@ -41,7 +41,8 @@ corr
{- ^ correlation
>>> corr (fromList[1,2,3]) (fromList [1..10])
fromList [14.0,20.0,26.0,32.0,38.0,44.0,50.0,56.0]
[14.0,20.0,26.0,32.0,38.0,44.0,50.0,56.0]
it :: (Enum t, Product t, Container Vector t) => Vector t
-}
corr ker v
Expand All @@ -54,7 +55,8 @@ conv :: (Container Vector t, Product t, Num t) => Vector t -> Vector t -> Vector
{- ^ convolution ('corr' with reversed kernel and padded input, equivalent to polynomial product)
>>> conv (fromList[1,1]) (fromList [-1,1])
fromList [-1.0,0.0,1.0]
[-1.0,0.0,1.0]
it :: (Product t, Container Vector t) => Vector t
-}
conv ker v
Expand Down
3 changes: 2 additions & 1 deletion packages/base/src/Internal/Matrix.hs
Original file line number Diff line number Diff line change
Expand Up @@ -160,7 +160,8 @@ extractAll ord m = unsafePerformIO (copy ord m)
{- | Creates a vector by concatenation of rows. If the matrix is ColumnMajor, this operation requires a transpose.
>>> flatten (ident 3)
fromList [1.0,0.0,0.0,0.0,1.0,0.0,0.0,0.0,1.0]
[1.0,0.0,0.0,0.0,1.0,0.0,0.0,0.0,1.0]
it :: (Num t, Element t) => Vector t
-}
flatten :: Element t => Matrix t -> Vector t
Expand Down
4 changes: 3 additions & 1 deletion packages/base/src/Internal/Sparse.hs
Original file line number Diff line number Diff line change
Expand Up @@ -172,8 +172,10 @@ gmXv Dense{..} v
{- | general matrix - vector product
>>> let m = mkSparse [((0,999),1.0),((1,1999),2.0)]
m :: GMatrix
>>> m !#> vector [1..2000]
fromList [1000.0,4000.0]
[1000.0,4000.0]
it :: Vector Double
-}
infixr 8 !#>
Expand Down
16 changes: 8 additions & 8 deletions packages/base/src/Internal/Static.hs
Original file line number Diff line number Diff line change
Expand Up @@ -324,34 +324,34 @@ isDiagg (Dim (Dim x))
instance KnownNat n => Show (R n)
where
show s@(R (Dim v))
| singleV v = "("++show (v!0)++" :: R "++show d++")"
| otherwise = "(vector"++ drop 8 (show v)++" :: R "++show d++")"
| singleV v = "(" ++ show (v!0) ++ " :: R " ++ show d ++ ")"
| otherwise = "(vector " ++ show v ++ " :: R " ++ show d ++")"
where
d = size s

instance KnownNat n => Show (C n)
where
show s@(C (Dim v))
| singleV v = "("++show (v!0)++" :: C "++show d++")"
| otherwise = "(vector"++ drop 8 (show v)++" :: C "++show d++")"
| singleV v = "(" ++ show (v!0) ++ " :: C " ++ show d ++ ")"
| otherwise = "(vector " ++ show v ++ " :: C " ++ show d ++")"
where
d = size s

instance (KnownNat m, KnownNat n) => Show (L m n)
where
show (isDiag -> Just (z,y,(m',n'))) = printf "(diag %s %s :: L %d %d)" (show z) (drop 9 $ show y) m' n'
show (isDiag -> Just (z,y,(m',n'))) = printf "(diag %s %s :: L %d %d)" (show z) (show y) m' n'
show s@(L (Dim (Dim x)))
| singleM x = printf "(%s :: L %d %d)" (show (x `atIndex` (0,0))) m' n'
| otherwise = "(matrix"++ dropWhile (/='\n') (show x)++" :: L "++show m'++" "++show n'++")"
| otherwise = "(matrix" ++ dropWhile (/='\n') (show x) ++ " :: L " ++ show m' ++ " " ++ show n' ++ ")"
where
(m',n') = size s

instance (KnownNat m, KnownNat n) => Show (M m n)
where
show (isDiagC -> Just (z,y,(m',n'))) = printf "(diag %s %s :: M %d %d)" (show z) (drop 9 $ show y) m' n'
show (isDiagC -> Just (z,y,(m',n'))) = printf "(diag %s %s :: M %d %d)" (show z) (show y) m' n'
show s@(M (Dim (Dim x)))
| singleM x = printf "(%s :: M %d %d)" (show (x `atIndex` (0,0))) m' n'
| otherwise = "(matrix"++ dropWhile (/='\n') (show x)++" :: M "++show m'++" "++show n'++")"
| otherwise = "(matrix" ++ dropWhile (/='\n') (show x) ++ " :: M " ++ show m' ++ " " ++ show n' ++ ")"
where
(m',n') = size s

Expand Down
6 changes: 4 additions & 2 deletions packages/base/src/Internal/Util.hs
Original file line number Diff line number Diff line change
Expand Up @@ -99,7 +99,8 @@ iC = 0:+1
{- | Create a real vector.
>>> vector [1..5]
fromList [1.0,2.0,3.0,4.0,5.0]
[1.0,2.0,3.0,4.0,5.0]
it :: Vector R
-}
vector :: [R] -> Vector R
Expand Down Expand Up @@ -378,7 +379,8 @@ size = size'
On a matrix it gets the k-th row as a vector:
>>> matrix 5 [1..15] ! 1
fromList [6.0,7.0,8.0,9.0,10.0]
[6.0,7.0,8.0,9.0,10.0]
it :: Vector Double
>>> matrix 5 [1..15] ! 1 ! 3
9.0
Expand Down
12 changes: 8 additions & 4 deletions packages/base/src/Internal/Vector.hs
Original file line number Diff line number Diff line change
Expand Up @@ -116,7 +116,8 @@ toList v = safeRead v $ peekArray (dim v)
be used, for instance, with infinite lists.
>>> 5 |> [1..]
fromList [1.0,2.0,3.0,4.0,5.0]
[1.0,2.0,3.0,4.0,5.0]
it :: (Enum a, Num a, Foreign.Storable.Storable a) => Vector a
-}
(|>) :: (Storable a) => Int -> [a] -> Vector a
Expand All @@ -135,7 +136,8 @@ idxs js = fromList (map fromIntegral js) :: Vector I
{- | takes a number of consecutive elements from a Vector
>>> subVector 2 3 (fromList [1..10])
fromList [3.0,4.0,5.0]
[3.0,4.0,5.0]
it :: (Enum t, Num t, Foreign.Storable.Storable t) => Vector t
-}
subVector :: Storable t => Int -- ^ index of the starting element
Expand Down Expand Up @@ -169,7 +171,8 @@ at' v n = safeRead v $ flip peekElemOff n
{- | concatenate a list of vectors
>>> vjoin [fromList [1..5::Double], konst 1 3]
fromList [1.0,2.0,3.0,4.0,5.0,1.0,1.0,1.0]
[1.0,2.0,3.0,4.0,5.0,1.0,1.0,1.0]
it :: Vector Double
-}
vjoin :: Storable t => [Vector t] -> Vector t
Expand All @@ -191,7 +194,8 @@ vjoin as = unsafePerformIO $ do
{- | Extract consecutive subvectors of the given sizes.
>>> takesV [3,4] (linspace 10 (1,10::Double))
[fromList [1.0,2.0,3.0],fromList [4.0,5.0,6.0,7.0]]
[[1.0,2.0,3.0],[4.0,5.0,6.0,7.0]]
it :: [Vector Double]
-}
takesV :: Storable t => [Int] -> Vector t -> [Vector t]
Expand Down
3 changes: 2 additions & 1 deletion packages/base/src/Internal/Vectorized.hs
Original file line number Diff line number Diff line change
Expand Up @@ -417,7 +417,8 @@ foreign import ccall unsafe "round_vector" c_round_vector :: TVV Double

-- |
-- >>> range 5
-- fromList [0,1,2,3,4]
-- [0,1,2,3,4]
-- it :: Vector I
--
range :: Int -> Vector I
range n = unsafePerformIO $ do
Expand Down
3 changes: 2 additions & 1 deletion packages/base/src/Numeric/LinearAlgebra.hs
Original file line number Diff line number Diff line change
Expand Up @@ -29,7 +29,8 @@ module Numeric.LinearAlgebra (
-- as the Hadamard product or the Schur product):
--
-- >>> vector [1,2,3] * vector [3,0,-2]
-- fromList [3.0,0.0,-6.0]
-- [3.0,0.0,-6.0]
-- it :: Vector R
--
-- >>> matrix 3 [1..9] * ident 3
-- (3><3)
Expand Down

0 comments on commit 2df7362

Please sign in to comment.