[Haskell-cafe] Error in converting List of Lists into PArray ( Parray a )

Atsuro Hoshino hoshinoatsuro at gmail.com
Thu Jan 19 00:16:37 CET 2012


Hi Mukesh,

Below is a naive implementation of converting `[[(Int,Double)]]' to
`PArray (PArray (Int, Double))' .
There's no instance for `PA [a]', I've explicitly separated the inner
and outer conversion.
Though, when reading data from a file and converting, it might be
better to use `hGet' in:

  http://hackage.haskell.org/packages/archive/dph-prim-par/0.5.1.1/doc/html/Data-Array-Parallel-Unlifted.html

-- 
module Main where

import Data.Array.Parallel
import Data.Array.Parallel.PArray ()
import qualified Data.Array.Parallel.PArray as P

mat_li :: [[(Int, Double)]]
mat_li =
  [ zip [1..] [ 1, 2, 3, 0, 0, 0, 0, 0, 4 ]
  , zip [1..] [ 0, 0, 0, 0, 0, 0, 0, 0, 0 ]
  , zip [1..] [ 0, 0, 0, 0, 0, 0, 1, 2, 0 ] ]

mat_pa_1 :: PArray (PArray (Int, Double))
mat_pa_1 = P.fromList (fmap P.fromList mat_li)

mat_pa_2 :: PArray (PArray (Int, Double))
mat_pa_2 = conv_outer (conv_inner mat_li)

conv_inner :: P.PA a => [[a]] -> [PArray a]
conv_inner = map P.fromList

conv_outer :: P.PA a => [PArray a] -> PArray (PArray a)
conv_outer xs = case xs of
  []     -> P.empty
  (x:xs) -> P.singleton x P.+:+ conv_outer xs

main :: IO ()
main =
  -- Printing `mat_pa_1' shows an error:
  --
  -- > No instance nor default method for class operation
  -- > Data.Array.Parallel.PArray.PData.fromListPR
  --
  -- print mat_pa_1
  print mat_pa_2

----

Hope this well help.


Regards,
 --
Atsuro Hoshino

On Thu, Jan 19, 2012 at 4:47 AM, mukesh tiwari
<mukeshtiwari.iiitm at gmail.com> wrote:
> Hello all
> I am trying to convert List of Lists ( [[(Int , Double )]] ) into PArray (
> PArray ( Int , Double )) but getting run time error. This code works fine
> and print list of PArray ( Int , Double ) but when i put print $ P.fromList
> ( map P.fromList c ) then i am getting runtime error. It says "Main:
> Data/Array/Parallel/PArray/PDataInstances.hs:337:10-30: No instance nor
> default method for class operation
> Data.Array.Parallel.PArray.PData.fromListPR". Could some one please tell me
> how to resolve this issue.
> Thank you
>
>
> --import ParallelMat
> import Data.List
> import System.Environment
> import Data.Array.Parallel
> import qualified Data.Array.Parallel.PArray as P
>
>
> processMatrix :: [ [ Double ] ] -> [ [ Double ] ] -> [ ( [ ( Int , Double )
> ] , [ ( Int , Double ) ]) ]
> processMatrix [] [] = []
> processMatrix ( x : xs ) ( y : ys )
>   | ( all ( == 0 ) x )  Prelude.|| (  all ( == 0 ) y ) = processMatrix xs ys
>   | otherwise = ( filter ( \( x , y ) -> y /= 0 ) . zip [ 1..]  $ x ,filter
> (  \( x , y ) -> y /= 0 ) . zip [1..] $ y  ) : processMatrix xs ys
>
> main = do
>     [ first , second ] <- getArgs
>     a <- readFile first
>     b <- readFile second
>     let a' = transpose . tail . map ( map ( read :: String -> Double ) .
> words ) . lines $ a
>         b' = tail . map ( map ( read :: String -> Double ) . words ) . lines
> $ b
>         ( c , d )   = unzip $ processMatrix a' b'
>     print $   (  map P.fromList c )
>    --print d
>
> Macintosh-0026bb610428:Haskell mukesh$ ghc --make  -Odph -fdph-par  Main.hs
> [1 of 1] Compiling Main             ( Main.hs, Main.o )
> Linking Main ...
> Macintosh-0026bb610428:Haskell mukesh$ ./Main  A.in A.in
> [fromList<PArray> [(1,1.0),(6,1.0)],fromList<PArray>
> [(4,11.0),(9,11.0)],fromList<PArray> [(1,4.0),(4,2.0),(6,4.0),(9,2.0)]]
>
> Putting print $ P.fromList ( map P.fromList c )
>
> Macintosh-0026bb610428:Haskell mukesh$ ghc --make  -Odph -fdph-par  Main.hs
> [1 of 1] Compiling Main             ( Main.hs, Main.o )
> Linking Main ...
> Macintosh-0026bb610428:Haskell mukesh$ ./Main  A.in A.in
> Main: Data/Array/Parallel/PArray/PDataInstances.hs:337:10-30: No instance
> nor default method for class operation
> Data.Array.Parallel.PArray.PData.fromListPR
>
> Input file A.in
> 10 10
> 1 2 3 0 0 0 0 0 0 4
> 0 0 0 0 0 0 0 0 0 0
> 0 0 0 0 0 0 0 0 0 0
> 0 0 0 0 0 0 1 2 11 2
> 0 1 2 0 0 0 0 0 0 0
> 1 2 3 0 0 0 0 0 0 4
> 0 0 0 0 0 0 0 0 0 0
> 0 0 0 0 0 0 0 0 0 0
> 0 0 0 0 0 0 1 2 11 2
> 0 1 2 0 0 0 0 0 0 0
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>



More information about the Haskell-Cafe mailing list