Skip to content

Commit fb62b8e

Browse files
committed
Merge branch 'oldmaster'
Commit which were missing after fixing problems with HG<->git mirroring Conflicts: .hgtags statistics.cabal
2 parents a3ae97a + 4b5c3e4 commit fb62b8e

File tree

2 files changed

+132
-3
lines changed

2 files changed

+132
-3
lines changed

Statistics/Matrix.hs

Lines changed: 120 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,4 @@
1+
{-# LANGUAGE PatternGuards #-}
12
-- |
23
-- Module : Statistics.Matrix
34
-- Copyright : 2011 Aleksey Khudyakov, 2014 Bryan O'Sullivan
@@ -9,13 +10,25 @@
910
-- we implement the necessary minimum here.
1011

1112
module Statistics.Matrix
12-
(
13+
( -- * Data types
1314
Matrix(..)
1415
, Vector
15-
, fromList
16+
-- * Conversion from/to lists/vectors
1617
, fromVector
18+
, fromList
19+
, fromRowLists
20+
, fromRows
21+
, fromColumns
1722
, toVector
1823
, toList
24+
, toRows
25+
, toColumns
26+
, toRowLists
27+
-- * Other
28+
, generate
29+
, generateSym
30+
, ident
31+
, diag
1932
, dimension
2033
, center
2134
, multiply
@@ -34,10 +47,21 @@ module Statistics.Matrix
3447
) where
3548

3649
import Prelude hiding (exponent, map, sum)
50+
import Control.Applicative ((<$>))
51+
import Control.Monad.ST
52+
import qualified Data.Vector.Unboxed as U
53+
import Data.Vector.Unboxed ((!))
54+
import qualified Data.Vector.Unboxed.Mutable as UM
55+
3756
import Statistics.Function (for, square)
3857
import Statistics.Matrix.Types
58+
import Statistics.Matrix.Mutable (unsafeNew,unsafeWrite,unsafeFreeze)
3959
import Statistics.Sample.Internal (sum)
40-
import qualified Data.Vector.Unboxed as U
60+
61+
62+
----------------------------------------------------------------
63+
-- Conversion to/from vectors/lists
64+
----------------------------------------------------------------
4165

4266
-- | Convert from a row-major list.
4367
fromList :: Int -- ^ Number of rows.
@@ -46,6 +70,10 @@ fromList :: Int -- ^ Number of rows.
4670
-> Matrix
4771
fromList r c = fromVector r c . U.fromList
4872

73+
-- | create a matrix from a list of lists, as rows
74+
fromRowLists :: [[Double]] -> Matrix
75+
fromRowLists = fromRows . fmap U.fromList
76+
4977
-- | Convert from a row-major vector.
5078
fromVector :: Int -- ^ Number of rows.
5179
-> Int -- ^ Number of columns.
@@ -56,6 +84,22 @@ fromVector r c v
5684
| otherwise = Matrix r c 0 v
5785
where len = U.length v
5886

87+
-- | create a matrix from a list of vectors, as rows
88+
fromRows :: [Vector] -> Matrix
89+
fromRows xs
90+
| [] <- xs = error "Statistics.Matrix.fromRows: empty list of rows!"
91+
| any (/=nCol) ns = error "Statistics.Matrix.fromRows: row sizes do not match"
92+
| nCol == 0 = error "Statistics.Matrix.fromRows: zero columns in matrix"
93+
| otherwise = fromVector nRow nCol (U.concat xs)
94+
where
95+
nCol:ns = U.length <$> xs
96+
nRow = length xs
97+
98+
99+
-- | create a matrix from a list of vectors, as columns
100+
fromColumns :: [Vector] -> Matrix
101+
fromColumns = transpose . fromRows
102+
59103
-- | Convert to a row-major flat vector.
60104
toVector :: Matrix -> U.Vector Double
61105
toVector (Matrix _ _ _ v) = v
@@ -64,6 +108,78 @@ toVector (Matrix _ _ _ v) = v
64108
toList :: Matrix -> [Double]
65109
toList = U.toList . toVector
66110

111+
-- | Convert to a list of lists, as rows
112+
toRowLists :: Matrix -> [[Double]]
113+
toRowLists (Matrix _ nCol _ v)
114+
= chunks $ U.toList v
115+
where
116+
chunks [] = []
117+
chunks xs = case splitAt nCol xs of
118+
(rowE,rest) -> rowE : chunks rest
119+
120+
121+
-- | Convert to a list of vectors, as rows
122+
toRows :: Matrix -> [Vector]
123+
toRows (Matrix _ nCol _ v) = chunks v
124+
where
125+
chunks xs
126+
| U.null xs = []
127+
| otherwise = case U.splitAt nCol xs of
128+
(rowE,rest) -> rowE : chunks rest
129+
130+
-- | Convert to a list of vectors, as columns
131+
toColumns :: Matrix -> [Vector]
132+
toColumns = toRows . transpose
133+
134+
135+
136+
----------------------------------------------------------------
137+
-- Other
138+
----------------------------------------------------------------
139+
140+
-- | Generate matrix using function
141+
generate :: Int -- ^ Number of rows
142+
-> Int -- ^ Number of columns
143+
-> (Int -> Int -> Double)
144+
-- ^ Function which takes /row/ and /column/ as argument.
145+
-> Matrix
146+
generate nRow nCol f
147+
= Matrix nRow nCol 0 $ U.generate (nRow*nCol) $ \i ->
148+
let (r,c) = i `quotRem` nCol in f r c
149+
150+
-- | Generate symmetric square matrix using function
151+
generateSym
152+
:: Int -- ^ Number of rows and columns
153+
-> (Int -> Int -> Double)
154+
-- ^ Function which takes /row/ and /column/ as argument. It must
155+
-- be symmetric in arguments: @f i j == f j i@
156+
-> Matrix
157+
generateSym n f = runST $ do
158+
m <- unsafeNew n n
159+
for 0 n $ \r -> do
160+
unsafeWrite m r r (f r r)
161+
for (r+1) n $ \c -> do
162+
let x = f r c
163+
unsafeWrite m r c x
164+
unsafeWrite m c r x
165+
unsafeFreeze m
166+
167+
168+
-- | Create the square identity matrix with given dimensions.
169+
ident :: Int -> Matrix
170+
ident n = diag $ U.replicate n 1.0
171+
172+
-- | Create a square matrix with given diagonal, other entries default to 0
173+
diag :: Vector -> Matrix
174+
diag v
175+
= Matrix n n 0 $ U.create $ do
176+
arr <- UM.replicate (n*n) 0
177+
for 0 n $ \i ->
178+
UM.unsafeWrite arr (i*n + i) (v ! i)
179+
return arr
180+
where
181+
n = U.length v
182+
67183
-- | Return the dimensions of this matrix, as a (row,column) pair.
68184
dimension :: Matrix -> (Int, Int)
69185
dimension (Matrix r c _ _) = (r, c)
@@ -125,6 +241,7 @@ unsafeIndex :: Matrix
125241
-> Double
126242
unsafeIndex = unsafeBounds U.unsafeIndex
127243

244+
-- | Apply function to every element of matrix
128245
map :: (Double -> Double) -> Matrix -> Matrix
129246
map f (Matrix r c e v) = Matrix r c e (U.map f v)
130247

Statistics/Matrix/Mutable.hs

Lines changed: 12 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -12,6 +12,7 @@ module Statistics.Matrix.Mutable
1212
, replicate
1313
, thaw
1414
, bounds
15+
, unsafeNew
1516
, unsafeFreeze
1617
, unsafeRead
1718
, unsafeWrite
@@ -37,6 +38,17 @@ thaw (Matrix r c e v) = MMatrix r c e <$> U.thaw v
3738
unsafeFreeze :: MMatrix s -> ST s Matrix
3839
unsafeFreeze (MMatrix r c e mv) = Matrix r c e <$> U.unsafeFreeze mv
3940

41+
-- | Allocate new matrix. Matrix content is not initialized hence unsafe.
42+
unsafeNew :: Int -- ^ Number of row
43+
-> Int -- ^ Number of columns
44+
-> ST s (MMatrix s)
45+
unsafeNew r c
46+
| r < 0 = error "Statistics.Matrix.Mutable.unsafeNew: negative number of rows"
47+
| c < 0 = error "Statistics.Matrix.Mutable.unsafeNew: negative number of columns"
48+
| otherwise = do
49+
vec <- M.new (r*c)
50+
return $ MMatrix r c 0 vec
51+
4052
unsafeRead :: MMatrix s -> Int -> Int -> ST s Double
4153
unsafeRead mat r c = unsafeBounds mat r c M.unsafeRead
4254
{-# INLINE unsafeRead #-}

0 commit comments

Comments
 (0)