[Haskell-cafe] [repa] beginner questions
Dmitry Malikov
malikov.d.y at gmail.com
Sun Nov 11 00:01:48 CET 2012
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
!
More information about the Haskell-Cafe
mailing list