Matlab Style Logic Operations ala V1.*(V2>0) on Vectors and Matrices with HMatrix ??

Hi all, In Matlab the following line of code: V3 = V1.*(V2>0) (V2>0) gives a Bool-Vector with ones (trues) and zero's where elements of V2 are > 0; Then this Bool vector is used to multiply all elements in V1 to zero where the condition V2>0 is not fulfilled. How can I do that in Haskell ? (I haven't seen bol operations or mapping functions into vectors, arrays in the HMatrix.pdf). . -- Many thanks in advance Phil -- View this message in context: http://haskell.1045720.n5.nabble.com/Matlab-Style-Logic-Operations-ala-V1-V2... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Mon, 20 Dec 2010, gutti wrote:
In Matlab the following line of code: V3 = V1.*(V2>0)
What you certainly need is a zipWith function on matrices that lets you write Matrix.zipWith (\a1 a2 -> if a2>0 then a1 else 0) v1 v2 I can't see such a function in Matrix, but in Vector (zipVectorWith) that can be lifted to Matrices by (Matrix.liftMatrix2). Maybe there is some magic type class that already handles this - if there wouldn't be the Element constraint, it would be the Applicative type class and the liftA2 function.

Hi Phil, On 12/20/2010 10:49 PM, gutti wrote:
Hi all,
In Matlab the following line of code: V3 = V1.*(V2>0)
(V2>0) gives a Bool-Vector with ones (trues) and zero's where elements of V2 are> 0; Then this Bool vector is used to multiply all elements in V1 to zero where the condition V2>0 is not fulfilled.
How can I do that in Haskell ? (I haven't seen bol operations or mapping functions into vectors, arrays in the HMatrix.pdf).
Vectorized boolean operations are not yet implemented but I hope to get them ready soon, including a "find" function. In the meantime you can use zipVectorWith, as mentioned by Henning. We could also use signum, but this is not recommended (signum 0 is 0): import Numeric.LinearAlgebra vec = fromList :: [Double] -> Vector Double cond x = (signum (x-scalar eps) + 1 ) / 2 v1 = vec [10..20] v2 = vec [-5..5] v3 = v1 * cond v2
v3 11 |> [0.0,0.0,0.0,0.0,0.0,0.0,16.0,17.0,18.0,19.0,20.0]
-Alberto
. -- Many thanks in advance Phil

On Tue, 21 Dec 2010, Alberto Ruiz wrote:
Vectorized boolean operations are not yet implemented but I hope to get them ready soon, including a "find" function. In the meantime you can use zipVectorWith, as mentioned by Henning.
I would not find it a great idea to support the MatLab style of handling booleans by 0 and 1. It's the whole point of Haskell's type safety to distinguish between numbers and booleans. MatLab even weakly distinguishs between numbers and booleans. If you use a vector of logical values (MatLab.logical corresponds to Haskell.Bool) as index, then it works like 'filter', e.g. logical indices: [1 2 3 4 5 6]([0 0 1 1 0 0]) = [3 4] number indices: [1 2 3 4 5 6]([0 0 1 1 0 0]) -> zero index not allowed Writing v2>0 in Haskell would mean to compare a matrix with a scalar. You would need a custom '>' operator and new type hacks in order to support all combinations of matrix and scalar operands. I think a Matrix.zipWith function would be the cleanest and most efficient way we can have!

Hi Henning, Hi Alberto, thanks for the quick and comprehensive help. - I managed to implement Hennings suggestion with mapVector and zipWithVector. -- However have a type inference problem with zipVectorWith -- probably a stupid beginners mistake. (have a look below). I want to look into the matrix thing as well, but that might take a bit. Its very good to hear that HMatrix develpment is going on and there are plans to implement more of Matlabs syntax. I see the point, that its probably not the "cleanest" way (bool to 0 & 1) but its damn convinient (laziness at its best). Maybe there could be a haskell way to implement the "lazy" matlab matrix and vector operation syntax (like explicit function for bool 2 num) Cheers Phil ######## Code import Numeric.LinearAlgebra import Graphics.Plot time = 101 |> [0, 0.1 .. 100 :: Double]; vector1 = sin(time); vector2 = vector1*0.9; posPart:: Vector Double -> Vector Double posPart v = mapVector (\a -> if a>=0 then a else 0) v v3:: Vector Double -> Vector Double -> Vector Double v3 v1 v2 = zipVectorWith(\a1 a2 -> if a1>=0 then a2/a1 else a1/a2) v1 v2 main = do -- print(v3) mplot [v3] mplot [posPart vector1] ### Compile error Couldn't match expected type `Vector Double' against inferred type `Vector Double -> Vector Double -> Vector Double' In the expression: v3 In the first argument of `mplot', namely `[v3]' In a stmt of a 'do' expression: mplot [v3] -- View this message in context: http://haskell.1045720.n5.nabble.com/Matlab-Style-Logic-Operations-ala-V1-V2... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

thanks for the quick and comprehensive help. - I managed to implement Hennings suggestion with mapVector and zipWithVector. -- However have a type inference problem with zipVectorWith -- probably a stupid beginners mistake. (have a look below). I want to look into the matrix thing as well, but that might take a bit.
It is Matrix.zipWith f x y = liftMatrix2 (zipVectorWith f) x y
I see the point, that its probably not the "cleanest" way (bool to 0 & 1) but its damn convinient (laziness at its best).
Is it really? Certainly, if you are used to. I am scared if someone multiplies the result of a comparison with something else. I find the 'if' most natural for such applications, and I like the Matrix.zipWith because it expresses that corresponding elements of matrices are combined and that it is no operation that is special for matrices (such as matrix multiplication or inversion or factorization or determinant).
Maybe there could be a haskell way to implement the "lazy" matlab matrix and vector operation syntax (like explicit function for bool 2 num)
You are free to implement any function, also higher order, also with infix syntax, that you need frequently. :-)
######## Code
import Numeric.LinearAlgebra import Graphics.Plot
time = 101 |> [0, 0.1 .. 100 :: Double];
vector1 = sin(time); vector2 = vector1*0.9;
I had to look twice, whether this is C or Haskell. It could be both of them. :-) I would certainly write: vector1, vector2 :: Vector Double vector1 = sin time vector2 = vector1*0.9
posPart:: Vector Double -> Vector Double posPart v = mapVector (\a -> if a>=0 then a else 0) v
How about: posPart = mapVector (max 0)
v3:: Vector Double -> Vector Double -> Vector Double v3 v1 v2 = zipVectorWith(\a1 a2 -> if a1>=0 then a2/a1 else a1/a2) v1 v2
main = do
-- print(v3) mplot [v3]
v3 is a function and 'mplot' seems to expect a vector.
mplot [posPart vector1]

Hi Henning, Yes I just realised my mistake myself - I hand over the function instead of the result. A really facinating concept by the way. Thanks again for the Matrix notation - will give it a go right away now. And the "manoever critics" on the code is really nice. - Helps me a lot to embrace the haskell syntax. One thing that still confuses me a litte: polynom: double -> double ->double polynom x y = y^2 + x^2 + 2*x*y Type declaration for this polynom with two inputs - what is input and what is output and which way a I supposed to read it ? -- x,y,polynom ? and when would I use double -> double => double Is there by the way the possibility in haskell to create functions with several outputs - ala Matlab function declation: function [N,k] = histogram(v,n) Hope I'm not asking too basic questions here, so feel free to point me to the right tutorial. Cheers Phil -- View this message in context: http://haskell.1045720.n5.nabble.com/Matlab-Style-Logic-Operations-ala-V1-V2... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Tue, 21 Dec 2010, gutti wrote:
One thing that still confuses me a litte:
polynom: double -> double ->double polynom x y = y^2 + x^2 + 2*x*y
Type declaration for this polynom with two inputs
I guess you mean upper case "Double", otherwise it's a type variable and the compiler will ask for type constraint like "polynom :: Num double => ..." Btw. the english word for the german "Polynom" is "polynomial". :-)
- what is input and what is output and which way a I supposed to read it ? -- x,y,polynom ? and when would I use double -> double => double
'polynom' is the function, 'x' and 'y' are its parameters (input), 'polynom x y' is the function value (output). The type 'double -> double => double' does not exist. The double arrow can be only at one place, immediately after the '::' and it separates the type constraints from the type expression. polynomialFunction :: Num a => a -> a -> a
Is there by the way the possibility in haskell to create functions with several outputs - ala Matlab function declation:
function [N,k] = histogram(v,n)
You can use pairs for results (and of course for arguments, too). See for instance: Prelude> :type divMod divMod :: (Integral a) => a -> a -> (a, a) What you cannot do in contrast to MatLab: You cannot omit function parameters in a function call, in a function implementation you cannot check for the number of parameters that the user has given actually (because the user cannot omit any argument at all), and you cannot check the number of requested output values. For me these restrictions are an advantage. In MatLab, a function can perform something completely different depending on the number of output or input values.
Hope I'm not asking too basic questions here, so feel free to point me to the right tutorial.
There's the haskell-beginners mailing list, but a good tutorial is certainly that by Hal Daume. http://www.haskell.org/haskellwiki/Yet_Another_Haskell_Tutorial However I see, that the URL http://darcs.haskell.org/yaht/yaht.pdf does not work any longer, certainly due to the recent server movement. :-( There is also various stuff at the Wiki: http://www.haskell.org/haskellwiki/Category:Idioms http://www.haskell.org/haskellwiki/Category:FAQ http://www.haskell.org/haskellwiki/Category:Glossary http://www.haskell.org/haskellwiki/Category:Style http://www.haskell.org/haskellwiki/Common_Misunderstandings http://www.haskell.org/haskellwiki/Haskell_programming_tips

Hi Henning, You definitly caught me on that little Germanism :-) About Your comments - a lot to learn and take in, but it really helps. - Thanks a lot. I just manged to get the Matrix masking running code looks like (code A see below). Two quick questions: question 1. u see the two commented lines I tried to get ur original line running, but didn't know how to specify f ## Code ######## import Numeric.LinearAlgebra import Graphics.Plot matrix1 = fromLists [[0 .. 5],[30 .. 35],[50 .. 55]] matrix2 = fromLists [[-1,2],[-3,4],[5,-6]] -- matrix1 = buildMatrix 3 4 ( (r,c) -> fromIntegral r * fromIntegral c) (3><4) -- posPart v = mapVector (\a -> if a>=0 then a else 0) v -- function2map a1 a2 = (\a1 a2 -> if a1>=0 then a2/a1 else a1/a2) matrixfunction x y = liftMatrix2 (zipVectorWith(\a1 a2 -> if a2>=0 then a1 else 0)) x y matrix3 = matrixfunction matrix1 matrix2 disp = putStr . disps 2 main = do disp matrix1 disp matrix2 -- disp matrix3 mesh matrix1 ######### question 2: - the compiler comes up with some weired data type problem -- ghci has no problem this line : matrixTest_Fail.hs:5:10: Ambiguous type variable `t' in the constraints: `Element t' arising from a use of `fromLists' at matrixTest_Fail.hs:5:10-38 `Num t' arising from the literal `1' at matrixTest_Fail.hs:5:22 Possible cause: the monomorphism restriction applied to the following: matrix2 :: Matrix t (bound at matrixTest_Fail.hs:5:0) Probable fix: give these definition(s) an explicit type signature or use -XNoMonomorphismRestriction ## Code ##### import Numeric.LinearAlgebra import Graphics.Plot matrix1 = fromLists [[1,2],[3,4],[5,6]] matrix2 = fromLists [[1,2],[3,4],[5,6]] disp = putStr . disps 2 main = do disp matrix1 ######### -- View this message in context: http://haskell.1045720.n5.nabble.com/Matlab-Style-Logic-Operations-ala-V1-V2... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Wed, 22 Dec 2010, gutti wrote:
question 1. u see the two commented lines I tried to get ur original line running, but didn't know how to specify f
What 'f' ? Do you mean matrixfunction f x y = liftMatrix2 (zipVectorWith f) x y ?
## Code ########
import Numeric.LinearAlgebra import Graphics.Plot
matrix1 = fromLists [[0 .. 5],[30 .. 35],[50 .. 55]] matrix2 = fromLists [[-1,2],[-3,4],[5,-6]]
-- matrix1 = buildMatrix 3 4 ( (r,c) -> fromIntegral r * fromIntegral c) (3><4) -- posPart v = mapVector (\a -> if a>=0 then a else 0) v
-- function2map a1 a2 = (\a1 a2 -> if a1>=0 then a2/a1 else a1/a2) matrixfunction x y = liftMatrix2 (zipVectorWith(\a1 a2 -> if a2>=0 then a1 else 0)) x y
matrix3 = matrixfunction matrix1 matrix2
disp = putStr . disps 2
main = do
disp matrix1 disp matrix2 -- disp matrix3 mesh matrix1
#########
question 2: - the compiler comes up with some weired data type problem -- ghci has no problem this line :
matrixTest_Fail.hs:5:10: Ambiguous type variable `t' in the constraints: `Element t' arising from a use of `fromLists' at matrixTest_Fail.hs:5:10-38 `Num t' arising from the literal `1' at matrixTest_Fail.hs:5:22 Possible cause: the monomorphism restriction applied to the following: matrix2 :: Matrix t (bound at matrixTest_Fail.hs:5:0) Probable fix: give these definition(s) an explicit type signature or use -XNoMonomorphismRestriction
## Code #####
import Numeric.LinearAlgebra import Graphics.Plot
matrix1 = fromLists [[1,2],[3,4],[5,6]] matrix2 = fromLists [[1,2],[3,4],[5,6]]
Before type inference can work, you need to fix the type of at least one number of a set of numbers with known equal type. E.g.
matrix1 = fromLists [[1,2],[3,4],[5,6::Double]]
or even better, add a type signature: matrix1 :: Matrix Double

Hi, Thanks for the help on the typing issue, that helped my understanding a lot. Regarding the lift2 Matrix: this line works : matrixfunction x y = liftMatrix2 (zipVectorWith(\a1 a2 -> if a2>=0 then a1 else 0)) x y but when I use this line : matrixfunction f x y = liftMatrix2 (zipVectorWith f) x y how can / do I have to define f in a seperate line a way, that it works and gives the same result ? Cheers Phil -- View this message in context: http://haskell.1045720.n5.nabble.com/Matlab-Style-Logic-Operations-ala-V1-V2... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

On Sat, 25 Dec 2010, gutti wrote:
this line works :
matrixfunction x y = liftMatrix2 (zipVectorWith(\a1 a2 -> if a2>=0 then a1 else 0)) x y
but when I use this line :
matrixfunction f x y = liftMatrix2 (zipVectorWith f) x y
how can / do I have to define f in a seperate line a way, that it works and gives the same result ?
The same way you have literally replaced (\a1 a2 -> if a2>=0 then a1 else 0) by 'f' at the right hand side, you can use that phrase as argument to the parameter 'f': matrixfunction (\a1 a2 -> if a2>=0 then a1 else 0) x y The lambda expression (\ ...) really is just a notation for a function.

Jep, finally got it - that code works now. The Problem I had at the end was that I didn't distinguish between type declaration of a function and a value. -- the commented line for matrix 3 below shows what I did wrong. I think we can close that topic for now - Thanks a lot for Your help Henning, Cheers Phil #### Code ###### import Numeric.LinearAlgebra import Graphics.Plot matrix1:: Matrix Double matrix1 = fromLists [[1,2],[3,4],[5,6]] matrix2:: Matrix Double matrix2 = fromLists [[-1,2],[-3,4],[5,-6]] funct:: Double -> Double -> Double funct = \a1 a2 -> if a2>=0 then a1 else 0 matrixfunction:: (Double -> Double -> Double) -> Matrix Double -> Matrix Double -> Matrix Double matrixfunction f x y = liftMatrix2 (zipVectorWith f ) x y matrix3:: Matrix Double -- matrix3 :: (Double -> Double -> Double) -> Matrix Double -> Matrix Double -> Matrix Double matrix3 = matrixfunction funct matrix1 matrix2 disp = putStr . disps 2 main = do disp matrix1 disp matrix3 -- View this message in context: http://haskell.1045720.n5.nabble.com/Matlab-Style-Logic-Operations-ala-V1-V2... Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
participants (3)
-
Alberto Ruiz
-
gutti
-
Henning Thielemann