Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Concatenating lists (Jan Erik Mostr?m)
   2.  Searching for word in 2D array (Nathan H?sken)
   3. Re:  Empty or Tree? (Angelos Sphyris)
   4. Re:  Searching for word in 2D array (Lorenzo Bolla)
   5. Re:  Searching for word in 2D array (Ozgur Akgun)
   6. Re:  Searching for word in 2D array (Nathan H?sken)
   7. Re:  Searching for word in 2D array (Lorenzo Bolla)


----------------------------------------------------------------------

Message: 1
Date: Thu, 22 Mar 2012 18:12:59 +0100
From: Jan Erik Mostr?m <li...@mostrom.pp.se>
Subject: Re: [Haskell-beginners] Concatenating lists
To: Thomas Davie <tom.da...@gmail.com>
Cc: beginners@haskell.org
Message-ID: <b9f98ae09c1349f98234c0a84832b...@jemostrom.com>
Content-Type: text/plain; charset="utf-8"



On 2012-03-22 at 17:11 , Thomas Davie wrote:

> When typing into the REPL, you can rebind values, because each subsequent 
> line appears (at least in the logical model) in an inner definition to the 
> past


Ahhh, I didn't know that. I'm probably a bit biased from previous ML/Python 
experiences. 
> My advice to you would be to stop thinking of trying to re-assign values 
> right now, it's not the correct way to think about a Haskell program at all.

No, I understand that ...  

Thanks for explaining.

- jem



------------------------------

Message: 2
Date: Thu, 22 Mar 2012 18:45:36 +0100
From: Nathan H?sken <nathan.hues...@posteo.de>
Subject: [Haskell-beginners] Searching for word in 2D array
To: beginners@haskell.org
Message-ID: <4f6b6540.7090...@posteo.de>
Content-Type: text/plain; charset=ISO-8859-1

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



------------------------------

Message: 3
Date: Thu, 22 Mar 2012 19:53:55 +0200
From: Angelos Sphyris <knightofmathemat...@hotmail.com>
Subject: Re: [Haskell-beginners] Empty or Tree?
To: <beginners@haskell.org>
Message-ID: <snt107-w27e5feb0b4a4eb9674f67ea5...@phx.gbl>
Content-Type: text/plain; charset="iso-8859-7"


 
>Someone correct 
> me, if I'm mistaken 
> but what seems to cause the problem is that the pattern matcher 
> needs constructors, so it can determine, whether a pattern can produce 
> an input data.
Yes, I would agree with you on that. It seems correct to me.
 
Angelos


 

> Date: Sat, 10 Mar 2012 12:45:07 +0100
> From: micha-scho...@web.de
> To: beginners@haskell.org
> Subject: Re: [Haskell-beginners] Empty or Tree?
> 
> > But when I try to create a more generic code like this which could work
> > with trees who don't have empty nodes in grandchild level :
> >
> > function Node a (Node b Tree Tree) (Node c Tree Tree )
> 
> The problem is that 'Tree' is a type, not a constructor. Someone correct 
> me, if I'm mistaken (this is my first post to the mailing-list, yieah 
> :-)), but what seems to cause the problem is that the pattern matcher 
> needs constructors, so it can determine, whether a pattern can produce 
> an input data.
> 
> There are several solutions. If you don't need the further subtrees, 
> leave them fully unspecified via the underscore:
> 
> function (Node a (Node b _ _) (Node c _ _)) = ...
> 
> or you could give them variable names like this:
> 
> function (Node a (Node b bl br) (Node c cl cr)) = ...
> 
> where bl, br, cl, and cr are variables of the type Tree. However, what 
> you might want to accomplish is a recursive function over the recursive 
> type to get a fully generic code. This usually looks something like this:
> 
> -- a generic recursive function
> cFunction :: Tree -> a
> cFunction Empty = ...
> cFunction (Node i l r) = f i (cFunction l) (cFunction r)
> where
> f :: Integer -> a -> a -> a
> f int recLeft recRight = ...
> 
> Hope that helped.
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
                                          
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120322/9981b84a/attachment-0001.htm>

------------------------------

Message: 4
Date: Thu, 22 Mar 2012 22:39:20 +0000
From: Lorenzo Bolla <lbo...@gmail.com>
Subject: Re: [Haskell-beginners] Searching for word in 2D array
To: Nathan H?sken <nathan.hues...@posteo.de>
Cc: beginners@haskell.org
Message-ID:
        <cadjgtrxjiaordygdkjog9xcmhyfmo3aob_dn7woq9vr-wd0...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Thu, Mar 22, 2012 at 5:45 PM, Nathan H?sken <nathan.hues...@posteo.de>wrote:

> 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
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120322/6adf2422/attachment-0001.htm>

------------------------------

Message: 5
Date: Fri, 23 Mar 2012 00:21:55 +0000
From: Ozgur Akgun <ozgurak...@gmail.com>
Subject: Re: [Haskell-beginners] Searching for word in 2D array
To: Nathan H?sken <nathan.hues...@posteo.de>
Cc: beginners@haskell.org
Message-ID:
        <CALzazPCVr58v1LMVc+0P=8pf6kjlml5bj66nhx-cejt+gv1...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

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
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120323/44a5debe/attachment-0001.htm>

------------------------------

Message: 6
Date: Fri, 23 Mar 2012 11:01:59 +0100
From: Nathan H?sken <nathan.hues...@posteo.de>
Subject: Re: [Haskell-beginners] Searching for word in 2D array
To: beginners@haskell.org
Message-ID: <4f6c4a17.20...@posteo.de>
Content-Type: text/plain; charset=UTF-8

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



------------------------------

Message: 7
Date: Fri, 23 Mar 2012 10:06:38 +0000
From: Lorenzo Bolla <lbo...@gmail.com>
Subject: Re: [Haskell-beginners] Searching for word in 2D array
To: Nathan H?sken <nathan.hues...@posteo.de>
Cc: beginners@haskell.org
Message-ID:
        <cadjgtrygp8td_nqs+kd2zo-8cv5qdjwnpufepu6ny9asvrb...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

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 <nathan.hues...@posteo.de>wrote:

> 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
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120323/f6afd03e/attachment.htm>

------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 45, Issue 29
*****************************************

Reply via email to