Re: [Haskell-cafe] [repa] beginner questions

2012-11-19 Thread Dmitry Malikov

On 11/19/2012 01:21 AM, Dominic Steinitz wrote:

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.


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


 Does that help?
Yep, kinda, this is a nice example of fromFunction usage, but my 
question was about retrieving indexing of elements that satisfy some 
predicate.


Thanks for response.

--
Best regards,
dmitry malikov
!


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


Re: [Haskell-cafe] [repa] beginner questions

2012-11-18 Thread Dominic Steinitz
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.


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


[Haskell-cafe] [repa] beginner questions

2012-11-10 Thread Dmitry Malikov

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?


2) How can I apply some function `f' to each row of 2D array `a' and 
collect results in single value?


f ∷ (Shape sh, Source r Bool) ⇒ Array r sh Bool → Bool
f a = (== toList a) $
  foldl1 (Prelude.zipWith (||)) $
  Prelude.map toList $
  foldl (\l k - filter (\x - x ! (Z :. k) == False) l) 
[b1,b2,b3,b4] $

  findWhich (== False) a

and ∷ [Bool] → Bool

[a1,a2] :: [Array U (Z :. Int) Bool]

Having all that I could find what I want like that:

and $ map f [a1,a2]
 True

All going on ridiculous and ugly because:

- 2D arrays are not 2D arrays but lists of 1D arrays

b1,b2,b3,b4,a1,a2 ∷ Array U (Z :. Int) Bool
b1 = fromListUnboxed (Z :. (3::Int)) [False, True, False]
b2 = fromListUnboxed (Z :. (3::Int)) [False, False, False]
b3 = fromListUnboxed (Z :. (3::Int)) [False, False, True]
b4 = fromListUnboxed (Z :. (3::Int)) [True, False, False]

a1 = fromListUnboxed (Z :. (3::Int)) [False, False, True]
a2 = fromListUnboxed (Z :. (3::Int)) [True, True, True]

How 2D array could be split to list of 1D arrays?

- redundant usage of `toList'; all operations are list-specified. How 
`f' could be rewritten in REPA terms?


--
Best regards,
dmitry malikov
!


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