[Haskell-cafe] [repa] beginner questions

Dominic Steinitz dominic at steinitz.org
Sun Nov 18 22:21:18 CET 2012


Dmitry Malikov <malikov.d.y <at> gmail.com> writes:

> 
> Playing around with repa arrays and got some questions.
> 
> 1) How I can get list of indexes of array that suffice some predicate?
> 
>      > a1
>      AUnboxed (Z :. 3) (fromList [False,False,True])
>      it :: Array U (Z :. Int) Bool
> 
> Indexes of element that satisfying specific predicate could be obtained 
> like that:
> 
>      > (\a p → Data.List.map (subtract 1 . snd) $ filter (p . fst) $ zip 
> (toList a) [1..]) a1 (== False)
>      [0,1]
> 
> Looks ugly. How REPA users used to do filtering like that without 
> converting to list?
> 

I hope someone will correct me if I am wrong and furthermore I was not
entirely clear what you were trying to do but it seems to me that if you
want to filter out an unknown number of elements from a collection 
then repa is the wrong abstraction to use.

You can however filter out a known number of elements e.g.

xs = Repa.fromListUnboxed (Z :. 3) [1, 2, 3]

removeOne ix xs = Repa.fromFunction
                               (Z :. dx - 1)
                               (\(Z :. jx) -> xs ! (Z :. f jx))
       where
         Z :. dx = Repa.extent xs
         f jx | jx < ix   = jx
               | otherwise = jx + 1

test = Repa.computeP $ removeOne 1 xs :: IO (Array U DIM1 Float)

Does that help?

Dominic.




More information about the Haskell-Cafe mailing list