[Haskell-cafe] parallel matrix multiply (dph, par/pseq)

Bertram Felgenhauer bertram.felgenhauer at googlemail.com
Mon Jan 18 09:34:12 EST 2010


Johannes Waldmann wrote:
> Hello.
> 
> How can I multiply matrices (of Doubles)
> with dph (-0.4.0)?  (ghc-6.12.1)  -  I was trying
> 
> type Vector = [:Double:]
> type Matrix = [:Vector:]
> 
> times :: Matrix -> Matrix -> Matrix
> times a b =
>       mapP
>       ( \ row -> mapP ( \ col -> sumP ( zipWithP (*) row col  ) )
>                       ( transposeP b )
>       ) a
> 
> but there is no such thing as transposeP.

It's possible to implement transposeP as follows,

    {-# LANGUAGE PArr #-}
    ...
    import qualified Data.Array.Parallel.Prelude.Int as I
    
    transposeP :: Matrix -> Matrix
    transposeP a = let
        h = lengthP a
        w = lengthP (a !: 0)
        rh = I.enumFromToP 0 (h I.- 1) -- or [: 0 .. h I.- 1 :]
        rw = I.enumFromToP 0 (w I.- 1) -- or [: 0 .. w I.- 1 :]
      in
        if h == 0 then [: :]
                  else mapP (\y -> mapP (\x -> a !: x !: y) rh) rw

Maybe there is a better way?

Bertram



More information about the Haskell-Cafe mailing list