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:  recursion and pattern matching (Alia)
   2. Re:  recursion and pattern matching (Alia)
   3. Re:  recursion and pattern matching (Brent Yorgey)
   4. Re:  recursion and pattern matching (Brent Yorgey)
   5. Re:  Beginners Digest, Vol 40, Issue 27 (Bob Walters-LT)


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

Message: 1
Date: Tue, 18 Oct 2011 06:04:25 -0700 (PDT)
From: Alia <alia_kho...@yahoo.com>
Subject: Re: [Haskell-beginners] recursion and pattern matching
To: "beginners@haskell.org" <beginners@haskell.org>
Message-ID:
        <1318943065.85777.yahoomail...@web65712.mail.ac4.yahoo.com>
Content-Type: text/plain; charset=iso-8859-1

<snip Brent Yorgey's helpful advice>

I'm afraid my powers of abstraction are failing me, I managed to get the depth 
function ok

and along the way accidentally made a count (nodes) function:


sumTree :: (Num b) => Tree a b -> b
sumTree EmptyTree = 0
sumTree (Node _ value children) = value + sum (map sumTree children)

count :: Tree a b -> Int
count EmptyTree = 0
count (Node _ value children) = 1 + sum (map count children) 

depth :: Tree a b -> Int
depth EmptyTree = 0
depth (Node _ value []) = 1
depth (Node _ value children) = 1 + maximum (map depth children)


However, I'm stuck on the treeFold function given your function signature:

treeFold :: c -> (a -> b -> [c] -> c) -> Tree a b -> c


At first I read it as c is an output type and also the type of the accumulator,
?which addresses the EmptyTree scenario:


treeFold acc f EmptyTree = acc

So far so good. Now, the 2nd arg which is a function specification, takes
an a and b (for the name and value respectively) and a list of cs.
Now this is confusing to me because the value of b is actually desirable 

as an output type as well. Did you mean c to refer to a list of children.
If so then why didn't you write the func spec as:

treeFold :: b -> (a -> b -> [Tree a b] -> b) -> Tree a b -> b
Sorry to be so dense about this, but I wanted to clarify this issue before I 
ran 

off and started looking at Data.Monoid and Data.Foldable from Learn me a 
haskell (-:


AK



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

Message: 2
Date: Tue, 18 Oct 2011 06:22:05 -0700 (PDT)
From: Alia <alia_kho...@yahoo.com>
Subject: Re: [Haskell-beginners] recursion and pattern matching
To: "beginners@haskell.org" <beginners@haskell.org>
Message-ID:
        <1318944125.34504.yahoomail...@web65705.mail.ac4.yahoo.com>
Content-Type: text/plain; charset=iso-8859-1

Sorry, as soon as I sent my email below, I realized that c should remain 
arbitrary because we don't
yet know whatwe want (if the function is to be truly pluggable) so you were 
probably right in your 

initial signature (I think).

so:


treeFold :: c -> (a -> b -> [c] -> c) -> Tree a b -> c


c is the target accumulator and the following still holds:

treeFold acc f EmptyTree = acc
But then unless we apply some function that recurses into the
tree and generates [c] shouldn't the signature of f be:

f :: (a -> b -> [Tree a b] -> c)


so that:

treeFold :: c -> (a -> b -> [Tree a b] -> c) -> Tree a b -> c

where we use the inital c as the accumulator and our
function folds the tree into the intermediate c values to 

ultimately reduce to the output c..

or am I completely off?

AK



----- Original Message -----
From: Alia <alia_kho...@yahoo.com>
To: "beginners@haskell.org" <beginners@haskell.org>
Cc: 
Sent: Tuesday, October 18, 2011 4:04 PM
Subject: re: [Haskell-beginners] recursion and pattern matching 

<snip Brent Yorgey's helpful advice>

I'm afraid my powers of abstraction are failing me, I managed to get the depth 
function ok

and along the way accidentally made a count (nodes) function:


sumTree :: (Num b) => Tree a b -> b
sumTree EmptyTree = 0
sumTree (Node _ value children) = value + sum (map sumTree children)

count :: Tree a b -> Int
count EmptyTree = 0
count (Node _ value children) = 1 + sum (map count children) 

depth :: Tree a b -> Int
depth EmptyTree = 0
depth (Node _ value []) = 1
depth (Node _ value children) = 1 + maximum (map depth children)


However, I'm stuck on the treeFold function given your function signature:

treeFold :: c -> (a -> b -> [c] -> c) -> Tree a b -> c


At first I read it as c is an output type and also the type of the accumulator,
?which addresses the EmptyTree scenario:


treeFold acc f EmptyTree = acc

So far so good. Now, the 2nd arg which is a function specification, takes
an a and b (for the name and value respectively) and a list of cs.
Now this is confusing to me because the value of b is actually desirable 

as an output type as well. Did you mean c to refer to a list of children.
If so then why didn't you write the func spec as:

treeFold :: b -> (a -> b -> [Tree a b] -> b) -> Tree a b -> b
Sorry to be so dense about this, but I wanted to clarify this issue before I 
ran 

off and started looking at Data.Monoid and Data.Foldable from Learn me a 
haskell (-:


AK




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

Message: 3
Date: Tue, 18 Oct 2011 09:25:03 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] recursion and pattern matching
To: beginners@haskell.org
Message-ID: <20111018132503.ga12...@seas.upenn.edu>
Content-Type: text/plain; charset=iso-8859-1

Hi Alia,

On Tue, Oct 18, 2011 at 06:04:25AM -0700, Alia wrote:
> <snip Brent Yorgey's helpful advice>
> 
> I'm afraid my powers of abstraction are failing me, I managed to get the 
> depth function ok
> 
> and along the way accidentally made a count (nodes) function:
> 
> 
> sumTree :: (Num b) => Tree a b -> b
> sumTree EmptyTree = 0
> sumTree (Node _ value children) = value + sum (map sumTree children)
> 
> count :: Tree a b -> Int
> count EmptyTree = 0
> count (Node _ value children) = 1 + sum (map count children) 
> 
> depth :: Tree a b -> Int
> depth EmptyTree = 0
> depth (Node _ value []) = 1
> depth (Node _ value children) = 1 + maximum (map depth children)

Great!  You could also make this a bit more modular by defining

  maximum0 [] = 0
  maximum0 xs = maximum xs

so that maximum0 handles the special case for the empty list of
children, then you could just get rid of the second case for depth and
use maximum0 in the last case.

> However, I'm stuck on the treeFold function given your function signature:
> 
> treeFold :: c -> (a -> b -> [c] -> c) -> Tree a b -> c
> 
> 
> At first I read it as c is an output type and also the type of the 
> accumulator,
> ?which addresses the EmptyTree scenario:
> 
> 
> treeFold acc f EmptyTree = acc

Yes, that's right.

> 
> So far so good. Now, the 2nd arg which is a function specification, takes
> an a and b (for the name and value respectively) and a list of cs.
> Now this is confusing to me because the value of b is actually desirable 
> as an output type as well. 

Yes, b *could* be desirable as an output type.  But that's OK, because
there is nothing stopping us from using the same type for both b and
c.  This way (using different type variables for b and c) someone can
use treeFold no matter whether they want the output type to be the
same or different than the type of the values.  It is perfectly
OK for different type variables to end up being the same type.  So
this version with both b and c is as general as possible.  If we made
b and c the same, treeFold would be less useful because there would be
some situations where you could not use it.

> Did you mean c to refer to a list of children.

Not quite. [c] refers to the list of *outputs* from calling treeFold
recursively on the children.

> If so then why didn't you write the func spec as:
> 
> treeFold :: b -> (a -> b -> [Tree a b] -> b) -> Tree a b -> b

This would not be a fold at all.  The point of a fold is that we
recursively fold any recursive substructures, and then say how to
combine the *outputs* from the folded substructures, not how to
combine the substructures themselves (which is what your type above
says).  Does that make sense?

> Sorry to be so dense about this, but I wanted to clarify this issue before I 
> ran 
> off and started looking at Data.Monoid and Data.Foldable from Learn
> me a haskell (-:

You're not being dense, this stuff takes some getting used to. And
yes, making sure you understand this before going on to read about
Foldable is probably wise (although you shouldn't have any problems
with Monoid).

It's hard to know whether I am explaining something well over email.
Do my explanations above make sense, or are you still confused?

-Brent



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

Message: 4
Date: Tue, 18 Oct 2011 09:30:55 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] recursion and pattern matching
To: beginners@haskell.org
Message-ID: <20111018133054.gb12...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Tue, Oct 18, 2011 at 06:22:05AM -0700, Alia wrote:
> Sorry, as soon as I sent my email below, I realized that c should remain 
> arbitrary because we don't
> yet know whatwe want (if the function is to be truly pluggable) so you were 
> probably right in your 
> 
> initial signature (I think).

Exactly right.

> But then unless we apply some function that recurses into the
> tree and generates [c] ...

You are on the right track here although you seem not to realize it. =)
Look at your implementations of treeSum, depth, etc. for inspiration...

-Brent



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

Message: 5
Date: Tue, 18 Oct 2011 07:46:22 -0700
From: Bob Walters-LT <b...@logictrust.com>
Subject: Re: [Haskell-beginners] Beginners Digest, Vol 40, Issue 27
To: beginners@haskell.org
Message-ID: <64f92d03-2b76-42c2-b90c-1aef1d66c...@logictrust.com>
Content-Type: text/plain; charset=us-ascii

please unsubscribe



On Oct 18, 2011, at 6:04 AM, beginners-requ...@haskell.org wrote:

> 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:  newbie: Monad, equivalent notation using
>      Control.Monad.guard (Brent Yorgey)
>   2. Re:  recursion and pattern matching (Brent Yorgey)
>   3. Re:  newbie: Monad, equivalent notation using
>      Control.Monad.guard (Hugo Ferreira)
>   4.  Weird (++) behavior when adding 2 vectors (Alexander Raasch)
>   5. Re:  Weird (++) behavior when adding 2 vectors (Vlad Hanciuta)
>   6. Re:  Weird (++) behavior when adding 2 vectors (Lorenzo Bolla)
>   7. Re:  Weird (++) behavior when adding 2 vectors (Amy de Buitl?ir)
>   8. Re:  Weird (++) behavior when adding 2 vectors (Alexander Raasch)
> 
> 
> ----------------------------------------------------------------------
> 
> Message: 1
> Date: Tue, 18 Oct 2011 06:52:01 -0400
> From: Brent Yorgey <byor...@seas.upenn.edu>
> Subject: Re: [Haskell-beginners] newbie: Monad, equivalent notation
>       using Control.Monad.guard
> To: beginners@haskell.org
> Message-ID: <20111018105201.ga1...@seas.upenn.edu>
> Content-Type: text/plain; charset=us-ascii
> 
> On Tue, Oct 18, 2011 at 10:52:57AM +0100, Hugo Ferreira wrote:
>> Hello,
>> 
>> On 10/17/2011 05:22 PM, Brent Yorgey wrote:
>>> On Mon, Oct 17, 2011 at 04:18:05PM +0100, Hugo Ferreira wrote:
>>>> Hello,
>>>> 
>>>> I came across the following code:
>>>> 
>>>> ngrams'' :: Int ->  [a] ->  [[a]]
>>>> ngrams'' n l = do
>>>>  t<- Data.List.tails l
>>>>  l<- [take n t]
>>>>  Control.Monad.guard (length l == n)
>>>>  return l
>>>> 
>>>> and tried to use the ">>=" operator in order
>>>> to figure out how Monads work. I came up with:
>>>> 
>>>> test l =
>>>>   (Data.List.tails l)
>>>>>> = (\t ->  [take 2 t])
>>>>>> = (\l ->  if (length l == 2) then [l] else [])
>>>> 
>>>> Questions:
>>>> 1. How can I use Control.Monad.guard directly in "test l"
>>> 
>>> test l =
>>>    (Data.List.tails l)
>>>>> = \t ->  [take 2 t]
>>>>> = \l ->  Control.Monad.guard (length l == 2)
>>>>>  return l
>>> 
>>> The rule is that
>>> 
>>>  x<- foo
>>> 
>>> desugars to
>>> 
>>>  foo>>= \x ->  ...
>>> 
>>> and
>>> 
>>>  blah
>>> 
>>> desugars to
>>> 
>>>  blah>>  ...
>>> 
>> 
>> Ok, I was not aware of the >>.
>> 
>>> One thing that might have been tripping you up is your extra
>>> parentheses around the lambda expressions.  If you have
>>> 
>>>>> = (\l ->  ...)
>>>>>  foo...
>>> 
>>> the l does not scope over foo... so you cannot mention it.  Instead
>>> what you want is
>>> 
>>>>> = \l ->  ...
>>>>>  foo...
>>> 
>>> so the lambda expression is actually   \l ->  ...>>  foo..., that is,
>>> it includes *everything* after the \l ->  ... and not just the stuff on
>>> that line.
>>> 
>> 
>> Hmmm. Still cannot wrap my mind around this B-(.
>> 
>> [[1],[2],[3]] >>= \l -> func1 l >>= \m -> func2 m
>> 
>> \l will hold each of the 3 elements of initial list
>>   these are concatenated with the results of func1
>>   results in a new list
>> 
>> \m will have each element in the new list
>>   these are concatenated with the results of func2
>>   results in a last list
>> 
>> is equal to ?
>> 
>> (([[1],[2],[3]] >>= \l -> func1 l) >>= \m -> func2 m)
> 
> Yes, your description is correct, and yes, these are equal. (Although
> the first is often more efficient.)  They are required to be equal by
> the monad laws. However, consider
> 
>  [[1],[2],[3]] >>= \l -> func1 l >>= \m -> func2 m l
> 
> and
> 
>  (([[1],[2],[3]] >>= \l -> func1 l) >>= \m -> func2 m l)
> 
> Notice that func2 now takes a second argument.  There is not even a
> question of whether these are equal: the second does not even compile,
> because the final 'l' is not in scope.  This is the point I was trying
> to make.
> 
> -Brent
> 
> 
> 
> ------------------------------
> 
> Message: 2
> Date: Tue, 18 Oct 2011 07:04:35 -0400
> From: Brent Yorgey <byor...@seas.upenn.edu>
> Subject: Re: [Haskell-beginners] recursion and pattern matching
> To: beginners@haskell.org
> Message-ID: <20111018110435.gb1...@seas.upenn.edu>
> Content-Type: text/plain; charset=iso-8859-1
> 
> On Tue, Oct 18, 2011 at 01:34:14AM -0700, Alia wrote:
>> I have a question about what's the idiomatic way to walk a tree where there 
>> is also a requirement
>> for pattern-matching to draw variables out of the Node 'container':
>> 
>> 
>> 
>> <Test.hs>
>> 
>> module Test
>> 
>> where
>> 
>> data Tree a b = EmptyTree | Node a b [Tree a b] 
>> ??????????? deriving (Show, Read, Eq)? 
>> ? 
>> t =? Node "goal" 1.0 [
>> ??????? Node "c1" 0.5 [
>> ??????????? Node "c3" 3.0 [
>> ??????????????? Node "c5" 1.0 []
>> ??????????????? ]
>> ??????????? ],
>> ??????? Node "c2" 0.5 [
>> ??????????? Node "c4" 2.0 []
>> ??????????? ]
>> ???? ]
>> 
>> 
>> sumTree :: (Num b) => Tree a b -> b
>> sumTree EmptyTree = 0
>> sumTree (Node _ value []) = value
>> sumTree (Node _ value [x]) = value + sumTree x
>> sumTree (Node name value (x:xs)) = value + sumTree x + sumTree (Node name 0 
>> xs)
>> 
>> depth :: Tree a b -> Int
>> depth EmptyTree = 0
>> depth (Node _ _ []) = 1
>> depth (Node _ _ [x]) = 1 + depth x
>> depth (Node n v (x:xs)) = 1 + depth (Node n v xs)?
>> 
>> </Test.hs>
>> 
>> Interactively:
>> 
>> *Test> sumTree t
>> 8.0
>> *Test> depth t
>> 4
>> *Test> 
>> 
>> 
>> This seems to work, but I have a sense that one should use folds and fmap 
>> and that there
>> is a better and cleaner what to do this.
> 
> Your sense is absolutely right! =)  You are not taking advantage of
> the fact that [] is a functor and can be folded over, etc. -- you have
> essentially hardcoded a list fold into your sumTree and depth
> functions.  First let's rewrite sumTree. We use 'map' to call
> 'sumTree' recursively on all the child trees, then sum the results:
> 
>  sumTree :: (Num b) => Tree a b -> b
>  sumTree EmptyTree = 0
>  sumTree (Node _ value children) = value + sum (map sumTree children)
> 
> Tada!  We handled all those list cases (empty, single element, or
> cons) at once, in a general way.
> 
> By the way, your implementation of 'depth' seems to be wrong: it only
> cares about the depth of the last child.  I would think the idea would
> be to take the maximum depth of all the children and add one to that.
> 
> I leave the rest for you:
> 
>  (1) rewrite depth in a similar way to sumTree, being sure to find
>      the maximum depth of all the children
> 
>  (2) generalize both sumTree and depth to a treeFold function:
> 
>        treeFold :: c -> (a -> b -> [c] -> c) -> Tree a b -> c
> 
>      The first argument says what to do with EmptyTree, and the
>      second argument says what to do with a Node.
> 
> Once you have implemented treeFold you should be able to implement
> both sumTree and depth in terms of treeFold.
> 
> Hope this helps. Let us know if you get stuck or have more questions!
> 
> -Brent
> 
> 
> 
> ------------------------------
> 
> Message: 3
> Date: Tue, 18 Oct 2011 13:07:57 +0100
> From: Hugo Ferreira <h...@inescporto.pt>
> Subject: Re: [Haskell-beginners] newbie: Monad, equivalent notation
>       using Control.Monad.guard
> To: Brent Yorgey <byor...@seas.upenn.edu>
> Cc: beginners@haskell.org
> Message-ID: <4e9d6c1d.7020...@inescporto.pt>
> Content-Type: text/plain; charset=ISO-8859-1; format=flowed
> 
> On 10/18/2011 11:52 AM, Brent Yorgey wrote:
>> On Tue, Oct 18, 2011 at 10:52:57AM +0100, Hugo Ferreira wrote:
>>> Hello,
>>> 
>>> On 10/17/2011 05:22 PM, Brent Yorgey wrote:
>>>> On Mon, Oct 17, 2011 at 04:18:05PM +0100, Hugo Ferreira wrote:
>>>>> Hello,
>>>>> 
>>>>> I came across the following code:
>>>>> 
>>>>> ngrams'' :: Int ->   [a] ->   [[a]]
>>>>> ngrams'' n l = do
>>>>>   t<- Data.List.tails l
>>>>>   l<- [take n t]
>>>>>   Control.Monad.guard (length l == n)
>>>>>   return l
>>>>> 
>>>>> and tried to use the ">>=" operator in order
>>>>> to figure out how Monads work. I came up with:
>>>>> 
>>>>> test l =
>>>>>    (Data.List.tails l)
>>>>>>> = (\t ->   [take 2 t])
>>>>>>> = (\l ->   if (length l == 2) then [l] else [])
>>>>> 
>>>>> Questions:
>>>>> 1. How can I use Control.Monad.guard directly in "test l"
>>>> 
>>>> test l =
>>>>     (Data.List.tails l)
>>>>>> = \t ->   [take 2 t]
>>>>>> = \l ->   Control.Monad.guard (length l == 2)
>>>>>>   return l
>>>> 
>>>> The rule is that
>>>> 
>>>>   x<- foo
>>>> 
>>>> desugars to
>>>> 
>>>>   foo>>= \x ->   ...
>>>> 
>>>> and
>>>> 
>>>>   blah
>>>> 
>>>> desugars to
>>>> 
>>>>   blah>>   ...
>>>> 
>>> 
>>> Ok, I was not aware of the>>.
>>> 
>>>> One thing that might have been tripping you up is your extra
>>>> parentheses around the lambda expressions.  If you have
>>>> 
>>>>>> = (\l ->   ...)
>>>>>>   foo...
>>>> 
>>>> the l does not scope over foo... so you cannot mention it.  Instead
>>>> what you want is
>>>> 
>>>>>> = \l ->   ...
>>>>>>   foo...
>>>> 
>>>> so the lambda expression is actually   \l ->   ...>>   foo..., that is,
>>>> it includes *everything* after the \l ->   ... and not just the stuff on
>>>> that line.
>>>> 
>>> 
>>> Hmmm. Still cannot wrap my mind around this B-(.
>>> 
>>> [[1],[2],[3]]>>= \l ->  func1 l>>= \m ->  func2 m
>>> 
>>> \l will hold each of the 3 elements of initial list
>>>    these are concatenated with the results of func1
>>>    results in a new list
>>> 
>>> \m will have each element in the new list
>>>    these are concatenated with the results of func2
>>>    results in a last list
>>> 
>>> is equal to ?
>>> 
>>> (([[1],[2],[3]]>>= \l ->  func1 l)>>= \m ->  func2 m)
>> 
>> Yes, your description is correct, and yes, these are equal. (Although
>> the first is often more efficient.)  They are required to be equal by
>> the monad laws. However, consider
>> 
>>   [[1],[2],[3]]>>= \l ->  func1 l>>= \m ->  func2 m l
>> 
>> and
>> 
>>   (([[1],[2],[3]]>>= \l ->  func1 l)>>= \m ->  func2 m l)
>> 
>> Notice that func2 now takes a second argument.  There is not even a
>> question of whether these are equal: the second does not even compile,
>> because the final 'l' is not in scope.  This is the point I was trying
>> to make.
> 
> Aaaah. Got it.
> 
> Thanks,
> Hugo F.
> 
>> 
>> -Brent
>> 
>> _______________________________________________
>> Beginners mailing list
>> Beginners@haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>> 
> 
> 
> 
> 
> ------------------------------
> 
> Message: 4
> Date: Tue, 18 Oct 2011 14:19:49 +0200
> From: Alexander Raasch <i...@alexraasch.de>
> Subject: [Haskell-beginners] Weird (++) behavior when adding 2 vectors
> To: beginners@haskell.org
> Message-ID: <4e9d6ee5.6090...@alexraasch.de>
> Content-Type: text/plain; charset=ISO-8859-1; format=flowed
> 
> Hi,
> 
> so I wrote this function to add two vectors represented as lists:
> 
> add a b = add' a b [] where
>     add' [] [] s = s
>     add' (a:as) (b:bs) s ++ [a+b]
> 
> OK, I tried this in ghci:
> 
>> add [1,2,3] [1,2,3]
> [6,4,2]
> 
> Hm, I expected the result to be [2,4,6], of course, since the currently 
> added components always go to the end of the resulting vector. I then 
> changed the last term in add' to
> 
> [a+b] ++ s ,
> 
> but still
> 
>> add [1,2,3] [1,2,3]
> [6,4,2]
> 
> Can anyone explain this behavior to me. I think there should be some 
> change in the result, no?
> 
> Alex
> 
> 
> 
> ------------------------------
> 
> Message: 5
> Date: Tue, 18 Oct 2011 14:36:40 +0200
> From: Vlad Hanciuta <wla...@gmail.com>
> Subject: Re: [Haskell-beginners] Weird (++) behavior when adding 2
>       vectors
> To: Alexander Raasch <i...@alexraasch.de>
> Cc: beginners@haskell.org
> Message-ID: <7c0687b5-7061-41e4-900c-fa0f1301b...@gmail.com>
> Content-Type: text/plain; charset=us-ascii
> 
> Hi,
> 
> Your code is not valid syntactically, I guess the last equation for add' is 
> "add' (a:as) (b:bs) s = add' as bs s ++ [a+b]". In that case, the function 
> application binds stronger that ++ operator so the expression is actually 
> equivalent to "(add' as bs s) ++ [a+b]". So you can easily see that the list 
> is computed backwards.
> 
> Vlad
> 
> On 18 Oct 2011, at 14:19, Alexander Raasch wrote:
> 
>> Hi,
>> 
>> so I wrote this function to add two vectors represented as lists:
>> 
>> add a b = add' a b [] where
>>   add' [] [] s = s
>>   add' (a:as) (b:bs) s ++ [a+b]
>> 
>> OK, I tried this in ghci:
>> 
>>> add [1,2,3] [1,2,3]
>> [6,4,2]
>> 
>> Hm, I expected the result to be [2,4,6], of course, since the currently 
>> added components always go to the end of the resulting vector. I then 
>> changed the last term in add' to
>> 
>> [a+b] ++ s ,
>> 
>> but still
>> 
>>> add [1,2,3] [1,2,3]
>> [6,4,2]
>> 
>> Can anyone explain this behavior to me. I think there should be some change 
>> in the result, no?
>> 
>> Alex
>> 
>> _______________________________________________
>> Beginners mailing list
>> Beginners@haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
> 
> 
> 
> 
> ------------------------------
> 
> Message: 6
> Date: Tue, 18 Oct 2011 13:48:40 +0100
> From: Lorenzo Bolla <lbo...@gmail.com>
> Subject: Re: [Haskell-beginners] Weird (++) behavior when adding 2
>       vectors
> To: Alexander Raasch <i...@alexraasch.de>
> Cc: beginners@haskell.org
> Message-ID:
>       <cadjgtrztafiymwfund8uyymw7djxvf-7snespn8w5hksm7m...@mail.gmail.com>
> Content-Type: text/plain; charset="utf-8"
> 
> Hi,
> 
> On Tue, Oct 18, 2011 at 1:19 PM, Alexander Raasch <i...@alexraasch.de>wrote:
> 
>> Hi,
>> 
>> so I wrote this function to add two vectors represented as lists:
>> 
>> add a b = add' a b [] where
>>   add' [] [] s = s
>>   add' (a:as) (b:bs) s ++ [a+b]
>> 
>> 
> I think something mangled your function, as this is not valid Haskell code.
> 
> Anyway, I tried to rewrite your function.
> The first version works as expected; the second gives reversed output.
> Note that there is no need for the accumulator "s".
> 
> add a b = add' a b
>        where add' [] [] = []
>              add' (a:as) (b:bs) = [a+b] ++ (add' as bs)
> 
> add a b = add' a b
>        where add' [] [] = []
>              add' (a:as) (b:bs) = (add' as bs) ++ [a+b] -- reversed output
> 
> Obviously, the same function can be written as:
> zipWith (+) [1,2,3] [1,2,3]
> 
> hth,
> L.
> -------------- next part --------------
> An HTML attachment was scrubbed...
> URL: 
> <http://www.haskell.org/pipermail/beginners/attachments/20111018/159bbe5b/attachment-0001.htm>
> 
> ------------------------------
> 
> Message: 7
> Date: Tue, 18 Oct 2011 12:51:27 +0000 (UTC)
> From: Amy de Buitl?ir <a...@nualeargais.ie>
> Subject: Re: [Haskell-beginners] Weird (++) behavior when adding 2
>       vectors
> To: beginners@haskell.org
> Message-ID: <loom.20111018t144110-...@post.gmane.org>
> Content-Type: text/plain; charset=us-ascii
> 
> There seems to be something missing from this line:
>>     add' (a:as) (b:bs) s ++ [a+b]
> 
> Assuming you want to write your own function as an exercise, you could write 
> it
> as a recursive function like this:
> 
> add [] b = b
> add a [] = a
> add (a:as) (b:bs) = (a+b) : (add as bs)
> 
> FYI, the easiest way to accomplish what you want is:
> 
> add = zipWith (+)
> 
> which is equivalent to:
> 
> add a b = zipWith (+) a b
> 
> 
> Hope that helps
> 
> 
> 
> 
> ------------------------------
> 
> Message: 8
> Date: Tue, 18 Oct 2011 15:04:25 +0200
> From: Alexander Raasch <i...@alexraasch.de>
> Subject: Re: [Haskell-beginners] Weird (++) behavior when adding 2
>       vectors
> To: beginners@haskell.org
> Message-ID: <4e9d7959.7090...@alexraasch.de>
> Content-Type: text/plain; charset="utf-8"; Format="flowed"
> 
> Hi,
> 
> thanks for your answers. I'm exercising with different programming 
> techniques, so the use of an accumulator was intentional although not 
> necessary. As Vlad said, my mistake was the stronger binding of the 
> function application. Sigh, ...
> 
> Thank you all again.
> 
> Alex
> 
> On 10/18/2011 02:48 PM, Lorenzo Bolla wrote:
>> Hi,
>> 
>> On Tue, Oct 18, 2011 at 1:19 PM, Alexander Raasch <i...@alexraasch.de 
>> <mailto:i...@alexraasch.de>> wrote:
>> 
>>    Hi,
>> 
>>    so I wrote this function to add two vectors represented as lists:
>> 
>>    add a b = add' a b [] where
>>       add' [] [] s = s
>>       add' (a:as) (b:bs) s ++ [a+b]
>> 
>> 
>> I think something mangled your function, as this is not valid Haskell 
>> code.
>> 
>> Anyway, I tried to rewrite your function.
>> The first version works as expected; the second gives reversed output.
>> Note that there is no need for the accumulator "s".
>> 
>> add a b = add' a b
>>        where add' [] [] = []
>>              add' (a:as) (b:bs) = [a+b] ++ (add' as bs)
>> 
>> add a b = add' a b
>>        where add' [] [] = []
>>              add' (a:as) (b:bs) = (add' as bs) ++ [a+b] -- reversed 
>> output
>> 
>> Obviously, the same function can be written as:
>> zipWith (+) [1,2,3] [1,2,3]
>> 
>> hth,
>> L.
> 
> -------------- next part --------------
> An HTML attachment was scrubbed...
> URL: 
> <http://www.haskell.org/pipermail/beginners/attachments/20111018/a500e224/attachment.htm>
> 
> ------------------------------
> 
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
> 
> 
> End of Beginners Digest, Vol 40, Issue 27
> *****************************************




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

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


End of Beginners Digest, Vol 40, Issue 28
*****************************************

Reply via email to