[Haskell-cafe] Matrices

2009-04-19 Thread Cetin Sert
http://ccnmtl.columbia.edu/projects/qmss/the_chisquare_test/about_the_chisquare_test.html

given two matrices,

Prelude Data.Matrix.Dense Data.Vector.Dense m
listMatrix (2,2) [46.0,37.0,71.0,83.0]
Prelude Data.Matrix.Dense Data.Vector.Dense es
listMatrix (2,2)
[40.9746835443038,42.0253164556962,76.0253164556962,77.9746835443038]

how can I flatten them to do:
[ (o-e)^2 / e | o - m, e - es ]

or use a function that will apply a given function to every
corresponding elements of 2 or n matrices and create a result matrix?

If I should use a different matrix type or library altogether, please
specify which one and how ^__^

Best Regards,
Cetin Sert
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Matrices

2009-04-19 Thread Alberto Ruiz

Using hmatrix-static:

import Numeric.LinearAlgebra.Static

m = [$mat| 46.0,37.0;
   71.0,83.0 |]

es = [$mat| 40.9746835443038,42.0253164556962;
76.0253164556962,77.9746835443038 |]

chisquare = sum . toList . flatten $ (m - es)^2 / es ::Double
--   1.8732940252518542

Cetin Sert wrote:

http://ccnmtl.columbia.edu/projects/qmss/the_chisquare_test/about_the_chisquare_test.html

given two matrices,

Prelude Data.Matrix.Dense Data.Vector.Dense m
listMatrix (2,2) [46.0,37.0,71.0,83.0]
Prelude Data.Matrix.Dense Data.Vector.Dense es
listMatrix (2,2)
[40.9746835443038,42.0253164556962,76.0253164556962,77.9746835443038]

how can I flatten them to do:
[ (o-e)^2 / e | o - m, e - es ]

or use a function that will apply a given function to every
corresponding elements of 2 or n matrices and create a result matrix?

If I should use a different matrix type or library altogether, please
specify which one and how ^__^

Best Regards,
Cetin Sert
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Matrices

2009-04-19 Thread Don Stewart
Very cool!

We need an hmatrix-static tutorial!

aruiz:
 Using hmatrix-static:

 import Numeric.LinearAlgebra.Static

 m = [$mat| 46.0,37.0;
71.0,83.0 |]

 es = [$mat| 40.9746835443038,42.0253164556962;
 76.0253164556962,77.9746835443038 |]

 chisquare = sum . toList . flatten $ (m - es)^2 / es ::Double
 --   1.8732940252518542

 Cetin Sert wrote:
 http://ccnmtl.columbia.edu/projects/qmss/the_chisquare_test/about_the_chisquare_test.html

 given two matrices,

 Prelude Data.Matrix.Dense Data.Vector.Dense m
 listMatrix (2,2) [46.0,37.0,71.0,83.0]
 Prelude Data.Matrix.Dense Data.Vector.Dense es
 listMatrix (2,2)
 [40.9746835443038,42.0253164556962,76.0253164556962,77.9746835443038]

 how can I flatten them to do:
 [ (o-e)^2 / e | o - m, e - es ]

 or use a function that will apply a given function to every
 corresponding elements of 2 or n matrices and create a result matrix?

 If I should use a different matrix type or library altogether, please
 specify which one and how ^__^

 Best Regards,
 Cetin Sert
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Matrices in Haskell

2007-07-22 Thread Ivan Lazar Miljenovic
On Tue, 2007-03-20 at 15:09 +1000, Matthew Brecknell wrote:

 I'm not sure I see the problem, since any operation that touches all the
 elements of a n-by-n matrix will be at least O(n^2). For such an
 operation, a transposition should just add a constant factor.

What I was hoping for was a data structure such that I could directly
access the columns of the matrix, rather than having to apply a function
to get to them.  I didn't think it likely, but then again, a man can
dream... ;)

 
 When you tried using Arrays, I presume you used an array indexed by a
 pair (i,j), and just reversed the order of the index pair to switch from
 row-wise to column-wise access? It's hard to see how that would slow you
 down. Perhaps the slowdown was caused by excessive array copying?
 Immutable arrays can be efficient for algorithms that write a whole
 array at once, but usually not for algorithms that modify one element at
 a time.
 
 I think you'll need to show specific functions that are performing below
 expectation before the list will be able to help.
 

I've attached the code I had written using Arrays.  Note that it wasn't
the final version of my algorithms, etc. as I continued work a bit
further using lists of lists, but the working behind them is just the
same (just some extra optimizations, etc. are missing).

Here's the way I was pulling out the rows and columns from the array:


type Matrix a = IArray MatCoord a
type MatCoord = (Int,Int)
type Row a = Array Int a

getRows :: Matrix a - [Row a]
getRows m = [newRow sr [(c,v) | ((r,c),v) - vals, r == r'] |
r' - values sr]
where
sr = fst . snd . bounds $ m
vals = assocs m

unRows :: [Row a] - Matrix a
unRows = liftM2 newMatrix length addRowValues
 where
 addRowValue r = map (\ (c,v) - ((r,c),v)) . assocs
 addRowValues = concat . zipWith addRowValue [1..]


getCols :: Matrix a - [Row a]
getCols m = [newRow sc [(r,v) | ((r,c),v) - vals, c == c'] |
c' - values sc]
where
sc = snd . snd . bounds $ m
vals = assocs m

unCols :: [Row a] - Matrix a
unCols = liftM2 newMatrix length addColValues
 where
 addColValue c = map (\ (r,v) - ((r,c),v)) . assocs
 addColValues = concat . zipWith addColValue [1..]

And here's an example where I used these functions.  What it's doing is
storing a list of all possible values for each cell in the matrix, then
removing double ups.

type Choices = [[Int]]

prune   :: Matrix Choices - Matrix Choices
prune =  pruneBy cols . pruneBy rows
 where 
 pruneBy (f,f') = f' . map reduce . f

reduce :: Row Choices - Row Choices
reduce r =  array size (map reducer vals)
where
size = bounds r
vals = assocs r
reducer (c,vs) = (c, vs `minus` singles)
singles = getSingles r

minus   :: Choices - Choices - Choices
xs `minus` ys   =  if single xs then xs else xs \\ ys

 For problems like latin squares and sudoku, also try thinking outside
 the matrix. Do you really need to structure the problem in terms of
 rows and columns? What about a set of mutually-intersecting sets of
 cells?

I based my code upon the paper by Richard Bird and later implemented by
Graham Hutton.  I'm going to be re-writing it a bit, in terms of first
generating the shapes that the Partial Latin Squares can take, then
trying to fill in the numbers.  I have considered using a graph-theory
approach, but I have no idea where to even start to code it.
Fundamentally, I'm trying to generate all Partial Latin Squares that fit
a given criteria, so I need the rows/columns to ensure that I have no
more than one instance of each value in each row or column.

-- 
Ivan Lazar Miljenovic
Latin Squares Solver and Generator
==

Declaring this as a module
--

 module LatinSquares  where

Importing Modules
-

 import Data.List
 import Data.Maybe()
 import Control.Monad.List
 import Data.Array.IArray

Defining Types
--

There are two main storage structures used: Sets and Matrices.
Whilst both of these utilise underlying Haskell lists, this distinction
is used to separate the different uses.  Sets are used to store all possible
or given values in no particular order, whilst matrices are used to store 
elements in some order in a 2-dimensional fashion.

A matrix is defined as a list of rows, where each row is a list
of values.  Note that, due to this definition, matrices are not 
inherently defined as having the same number of items in each 
row and column: this is up to the function that creates the matrix!

 type Matrix a = IArray MatCoord a

 type MatCoord = (Int,Int)

 type Row a = Array Int a

A set is merely a collection of items of the same type

 type Set a = [a]

A Latin Square is defined as a matrix of values, with Value as a wrapper
around Int.  Choices is a set of values used to 

Re: [Haskell-cafe] Matrices in Haskell

2007-03-20 Thread Vincent Kraeutler
Matthew Brecknell wrote:
 Ivan Miljenovic:
   
 As such, I'd like to know if there's any way of storing a an n-by-n
 matrix such that the algorithm/function to get either the rows or the
 columns is less than O(n^2) like transposition is.  I did try using an
 Array, but my (admittedly hurried and naive) usage of them took longer
 than a list of lists, was more difficult to manipulate, and wasn't
 required separate inverse functions to row and cols.  Also, since I
 need to look all throughout the list of values, it's still O(n^2), but
 this time for both rows and columns.
 

 I'm not sure I see the problem, since any operation that touches all the
 elements of a n-by-n matrix will be at least O(n^2). For such an
 operation, a transposition should just add a constant factor.

 When you tried using Arrays, I presume you used an array indexed by a
 pair (i,j), and just reversed the order of the index pair to switch from
 row-wise to column-wise access? It's hard to see how that would slow you
 down. Perhaps the slowdown was caused by excessive array copying?
 Immutable arrays can be efficient for algorithms that write a whole
 array at once, but usually not for algorithms that modify one element at
 a time.

 I think you'll need to show specific functions that are performing below
 expectation before the list will be able to help.

 For problems like latin squares and sudoku, also try thinking outside
 the matrix. Do you really need to structure the problem in terms of
 rows and columns? What about a set of mutually-intersecting sets of
 cells?

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


   
i think you might also want to check up on

http://en.wikibooks.org/wiki/Haskell/Hierarchical_libraries/Arrays

if you intend to do a significant number of incremental updates, it is my
(not particularly well-informed) understanding that you should use either
mutable arrays (Data.Array.ST  together with runST), or Data.Array.Diff
with explicit sequencing.

both approaches are discussed in the above wikipedia entry.

cheers,
v.



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Matrices in Haskell

2007-03-20 Thread Claus Reinke

When you tried using Arrays, I presume you used an array indexed by a
pair (i,j), and just reversed the order of the index pair to switch from
row-wise to column-wise access? It's hard to see how that would slow you
down. Perhaps the slowdown was caused by excessive array copying?


the difference can be in locality wrt the memory hierarchy: is the next element
nearby most of the time (apart from array borders), or a row-/column-width 
away most of the time?


i understand that, eg, fortran and c differ in their default interpretations of array 
layout, so naively translated benchmarks might suffer from running against the 
grain in one of the two (row-major loops over a column-major layout, or the

other way round).

claus

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Matrices in Haskell

2007-03-20 Thread Vincent Kraeutler
Claus Reinke wrote:
 When you tried using Arrays, I presume you used an array indexed by a
 pair (i,j), and just reversed the order of the index pair to switch from
 row-wise to column-wise access? It's hard to see how that would slow you
 down. Perhaps the slowdown was caused by excessive array copying?

 the difference can be in locality wrt the memory hierarchy: is the
 next element
 nearby most of the time (apart from array borders), or a
 row-/column-width away most of the time?

 i understand that, eg, fortran and c differ in their default
 interpretations of array layout, so naively translated benchmarks
 might suffer from running against the grain in one of the two
 (row-major loops over a column-major layout, or the
 other way round).

 claus

 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe


it seems unlikely to me that this would cause a degradation in
performance with respect to lists...
or is there something very interesting to learn about the inner workings
of linked lists in ghc?

regards,
v.



signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Matrices in Haskell

2007-03-20 Thread Claus Reinke

it seems unlikely to me that this would cause a degradation in
performance with respect to lists...


that might depend on the number of operations per transposition, i guess. 


lists and explicit transpositions make it very obvious what is going on in 
terms of
iteration order, so i would be tempted to group operations by whether they need
a plain or transposed structure. arrays hide this kind of thing, so i might pay 
the
cost for every transposed operation without the code warning me.

the original poster was doing (transpose . op . transpose) for each out-of-order 
op in the list version, so that might be on par with what the array version does, or

not. optimising array computations is a fun business.

but i misread the part i quoted to talk about slowdown on switching between 
row-column and column-row, whereas it was generally about slowdown on 
switching variable-order operations from lists to arrays. so i assume that posters

here were already aware of the transposition of layout affecting arrays as well.

claus

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Matrices in Haskell

2007-03-19 Thread Ivan Miljenovic

Some of you might recall me annoying people on #haskell over the New
Year about my Latin Squares project.  Well, I'm looking at re-doing it
from scratch, but the first thing I need to do is find a new way of
representing my square.

I have been using a list of lists ([[a]]) to represent a matrix.  The
problem with this data structure is that I need to be able to
manipulate matrices as both row-oriented and column-oriented data
structures, as I need to examine the values in the columns as well as
in the rows.  As it stands, I was doing this by transposing the
matrix, manipulating it, then transposing it back again.  This is a
pain, as it takes up about 15% to 20% of the run time.  The other
problem with using a list of lists is that the only reason I'm sure
that the matrix is valid (i.e. all the rows are the same length, etc.)
is because I created it that way, not because the data structure
requires it.

As such, I'd like to know if there's any way of storing a an n-by-n
matrix such that the algorithm/function to get either the rows or the
columns is less than O(n^2) like transposition is.  I did try using an
Array, but my (admittedly hurried and naive) usage of them took longer
than a list of lists, was more difficult to manipulate, and wasn't
required separate inverse functions to row and cols.  Also, since I
need to look all throughout the list of values, it's still O(n^2), but
this time for both rows and columns.

I know that when doing something similar to this in Java a few years
ago (a primitive Sudoku solver, to be precise), I could represent the
rows and columns as to separate 2D arrays, with rows(i,j) pointing to
the same object as cols(j,i).  Is something like this possible in
Haskell?  in particular, I will be storing lists of possible values in
the cells of the matrix, so the capability to backtrack would be very
nice, as I'd be trying each value at a time to see if it is valid.

I'd also want to use such a matrix implementation next semester for a
project, which I plan on being a quick comparison of various
programming languages as to ease of use and efficiency for
matrix-based computing problems.

--
Ivan Lazar Miljenovic
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Matrices in Haskell

2007-03-19 Thread Matthew Brecknell
Ivan Miljenovic:
 As such, I'd like to know if there's any way of storing a an n-by-n
 matrix such that the algorithm/function to get either the rows or the
 columns is less than O(n^2) like transposition is.  I did try using an
 Array, but my (admittedly hurried and naive) usage of them took longer
 than a list of lists, was more difficult to manipulate, and wasn't
 required separate inverse functions to row and cols.  Also, since I
 need to look all throughout the list of values, it's still O(n^2), but
 this time for both rows and columns.

I'm not sure I see the problem, since any operation that touches all the
elements of a n-by-n matrix will be at least O(n^2). For such an
operation, a transposition should just add a constant factor.

When you tried using Arrays, I presume you used an array indexed by a
pair (i,j), and just reversed the order of the index pair to switch from
row-wise to column-wise access? It's hard to see how that would slow you
down. Perhaps the slowdown was caused by excessive array copying?
Immutable arrays can be efficient for algorithms that write a whole
array at once, but usually not for algorithms that modify one element at
a time.

I think you'll need to show specific functions that are performing below
expectation before the list will be able to help.

For problems like latin squares and sudoku, also try thinking outside
the matrix. Do you really need to structure the problem in terms of
rows and columns? What about a set of mutually-intersecting sets of
cells?

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe