
Hey, I have the following problem. I have an 2D array of letters, like this: b w y l a i l q h w r a o q e d Now I am searching for all occurrences of a specific word in this array. The word can be horizontal, vertical or diagonal, like "bird" is in the example above. I am a beginer at haskell and I do not know where to start ... OK, I would represent the word as an String == [Char] and my array as [[Char]] (or would some kind of fixed size array make more sense?). In an imperative program, I would just search for the first letter and than check the rest of the word in all directions. If I do this, I need direct indexing of the array. Any advise in which direction to think? Thanks! Nathan

On Thu, Mar 22, 2012 at 5:45 PM, Nathan Hüsken
Hey,
I have the following problem. I have an 2D array of letters, like this:
b w y l a i l q h w r a o q e d
Now I am searching for all occurrences of a specific word in this array. The word can be horizontal, vertical or diagonal, like "bird" is in the example above. I am a beginer at haskell and I do not know where to start ...
OK, I would represent the word as an String == [Char] and my array as [[Char]] (or would some kind of fixed size array make more sense?).
In an imperative program, I would just search for the first letter and than check the rest of the word in all directions. If I do this, I need direct indexing of the array.
Any advise in which direction to think?
What about using Vector (for fast indexing and slicing) and use a 1D array? Maybe something as simple as this? import Data.Vector hiding (elem) import Prelude hiding (length) ncols :: Int ncols = 4 row :: Int -> Vector a -> Vector a row i = slice (i * ncols) ncols col :: Int -> Vector a -> Vector a col i v = let idxs = [i, i + ncols .. length v] in ifilter (\i _ -> i `elem` idxs) v diag :: Int -> Vector a -> Vector a diag i v = let idxs = [i, i + ncols + 1 .. length v] in ifilter (\i _ -> i `elem` idxs) v v :: Vector Char v = fromList "bwylailqhwraoqed" main :: IO () main = do print v print $ row 0 v print $ col 0 v print $ diag 0 v L.
Thanks! Nathan
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hi, import Data.List import qualified Data.Set as S rows :: Ord a => [[a]] -> S.Set [a] rows = S.fromList cols :: Ord a => [[a]] -> S.Set [a] cols = S.fromList . transpose diagonals :: Ord a => [[a]] -> S.Set [a] diagonals [] = S.empty diagonals xss = S.union ( S.fromList $ transpose (zipWith drop [0..] xss) ) ( diagonals (map init (tail xss)) ) allWords :: Ord a => [[a]] -> S.Set [a] allWords xss = S.unions [ rows xss , cols xss , diagonals xss , diagonals (map reverse xss) ] Now you can do all sorts of things, since you have the set of all words at hand. The function you originally wanted, checking the existence of a word can be the following: search :: Ord a => [a] -> [[a]] -> Bool search word xss = not $ null [ () | xs <- S.toList (allWords xss), word `isPrefixOf` xs ] But I suppose a function which removes the found word from the set could be more useful. Please ask if you have any questions about the above code, I can try to elaborate. Hope this helps, Ozgur

Firstly, Thanks! I take from the both replies, to first create data-structures for rows, columns and diagonals. That approach makes sense to me. On 03/23/2012 01:21 AM, Ozgur Akgun wrote:
Hi,
import Data.List import qualified Data.Set as S
rows :: Ord a => [[a]] -> S.Set [a] rows = S.fromList
cols :: Ord a => [[a]] -> S.Set [a] cols = S.fromList . transpose
diagonals :: Ord a => [[a]] -> S.Set [a] diagonals [] = S.empty diagonals xss = S.union ( S.fromList $ transpose (zipWith drop [0..] xss) ) ( diagonals (map init (tail xss)) )
allWords :: Ord a => [[a]] -> S.Set [a] allWords xss = S.unions [ rows xss , cols xss , diagonals xss , diagonals (map reverse xss) ]
... search :: Ord a => [a] -> [[a]] -> Bool search word xss = not $ null [ () | xs <- S.toList (allWords xss), word `isPrefixOf` xs ]
If I understand correctly, in this solution it is assumed that that a word must be a complete line (row column or diagonal), correct? I was not clear in original mail, the word can also be in the middle of line, but it seems easy enough to adjust the sample for this. I do not understand why a set is used. Couldn't just a list be used here, or is there some performance advantage I do not see? I find it very difficult to estimate the performance of an haskell program. The other solution of Lorenzo Bolla utilizes Data.Vector. Does that give a performance advantage in this case? Thanks! Nathan

I'm not sure Data.Set would work, because afaik, Sets don't preserve
ordering: so a row like "abc" and "cab" would be represented by the same
Set.
Data.Vector is more efficient, but I like it more than List when I have to
do slicing.
hth,
L.
On Fri, Mar 23, 2012 at 10:01 AM, Nathan Hüsken
Firstly, Thanks! I take from the both replies, to first create data-structures for rows, columns and diagonals. That approach makes sense to me.
On 03/23/2012 01:21 AM, Ozgur Akgun wrote:
Hi,
import Data.List import qualified Data.Set as S
rows :: Ord a => [[a]] -> S.Set [a] rows = S.fromList
cols :: Ord a => [[a]] -> S.Set [a] cols = S.fromList . transpose
diagonals :: Ord a => [[a]] -> S.Set [a] diagonals [] = S.empty diagonals xss = S.union ( S.fromList $ transpose (zipWith drop [0..] xss) ) ( diagonals (map init (tail xss)) )
allWords :: Ord a => [[a]] -> S.Set [a] allWords xss = S.unions [ rows xss , cols xss , diagonals xss , diagonals (map reverse xss) ]
... search :: Ord a => [a] -> [[a]] -> Bool search word xss = not $ null [ () | xs <- S.toList (allWords xss), word `isPrefixOf` xs ]
If I understand correctly, in this solution it is assumed that that a word must be a complete line (row column or diagonal), correct? I was not clear in original mail, the word can also be in the middle of line, but it seems easy enough to adjust the sample for this.
I do not understand why a set is used. Couldn't just a list be used here, or is there some performance advantage I do not see?
I find it very difficult to estimate the performance of an haskell program. The other solution of Lorenzo Bolla utilizes Data.Vector. Does that give a performance advantage in this case?
Thanks! Nathan
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

On 23 March 2012 10:06, Lorenzo Bolla
I'm not sure Data.Set would work, because afaik, Sets don't preserve ordering: so a row like "abc" and "cab" would be represented by the same Set.
What? Yes, Data.Set doesn't preserve any ordering between the members of it. It doesn't modify the members themselves and shuffle their content though. Try it for yourself: ghci> S.fromList ["abc", "cab"] ghci> S.fromList ["abc", "cab", "abc"] Ozgur

On 23 March 2012 10:01, Nathan Hüsken
If I understand correctly, in this solution it is assumed that that a word must be a complete line (row column or diagonal), correct?
No it doesn't. See the "search" function and the use of isInfixOf there.
I do not understand why a set is used. Couldn't just a list be used here, or is there some performance advantage I do not see?
You certainly can use a list in this case. However, if you do not care about the number of times a word appears in a collection (which seemed to be the case here), then using a Set might be a better idea. You can implement the same thing using lists instead of sets and see it for yourself :)
I find it very difficult to estimate the performance of an haskell program. The other solution of Lorenzo Bolla utilizes Data.Vector. Does that give a performance advantage in this case?
I don't use a lot of Vectors, so no comment here. Cheers, Ozgur
participants (3)
-
Lorenzo Bolla
-
Nathan Hüsken
-
Ozgur Akgun