I was trying to use the array comprehension of the Data Parallel
Haskell package.

http://haskell.org/haskellwiki/GHC/Data_Parallel_Haskell

for instance I can define

{-# OPTIONS -fparr -fglasgow-exts #-}

module MatTest
where
import GHC.PArr

ident = [:[:1,0:],[:0,1:]:]
aVect = [:4,5:]

dotP :: Num a => [:a:] -> [:a:] -> a
dotP xs ys = sumP [:x * y | x <- xs | y <- ys :]

matVecMul :: Num a => [:[:a:]:] -> [:a:] -> [:a:]
matVecMul xs ys = [:dotP x ys | x <- xs:]


but when I tried to define a matrix matrix multiplication

matMel :: Num a => [:[:a:]:] -> [:[:a:]:] -> [:a:]

I was at a loss for how to do it because i couldn't define transpose.

On 4/18/07, Henning Thielemann <[EMAIL PROTECTED]> wrote:

On Wed, 18 Apr 2007, Chris Witte wrote:

> I just started playing around with GHC.PArr and array comprehension
> and I was wondering if there is a way to define the transpose of a
> matrix using array comprehension?

Why not

  let swap :: (i,j) -> (j,i)
      swap (a,b) = (b,a)
  in  ixmap (let (lower,upper) = bounds arr in (swap lower, swap upper))
            swap arr

?

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

Reply via email to