Send Beginners mailing list submissions to
        [email protected]

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
        [email protected]

You can reach the person managing the list at
        [email protected]

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


Today's Topics:

   1. Re:  Is foldr slow? (Daniel Fischer)
   2. Re:  numerical integration over lists (Henk-Jan van Tuyl)
   3. Re:  yet another monad question (Ovidiu Deac)
   4. Re:  numerical integration over lists (Thomas Engel)
   5. Re:  numerical integration over lists (Benjamin Edwards)
   6. Re:  numerical integration over lists (Daniel Fischer)


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

Message: 1
Date: Sun, 5 Feb 2012 14:25:29 +0100
From: Daniel Fischer <[email protected]>
Subject: Re: [Haskell-beginners] Is foldr slow?
To: [email protected]
Message-ID: <[email protected]>
Content-Type: Text/Plain;  charset="iso-8859-1"

On Sunday 05 February 2012, 11:33:35, Zhi-Qiang Lei wrote:
> Thank you very much. You are right. foldl performs much better here. I
> thought foldr always has a performance advantage due to its tail
> recursion.

Firstly, tail recursion isn't automatically better in Haskell. Due to 
laziness, the evaluation sequence is different from what it'd be in eager 
languages, and not necessarily the order in which the steps are written in 
the code.

If the recursive call to a (non tail-recursive) function is in a lazy 
argument position of the result, a lot of evaluation can take place before 
the recursive call is demanded.

A tail recursive function on the other hand cannot deliver any part of the 
result before the recursion is completed.

Secondly, foldr is not tail recursive, foldl is:

foldr f z (x:xs) = x `f` (foldr f z xs)

foldl f z (x:xs) = foldl f (f z x) xs

Thus if 'f' is lazy in its second argument, like for example (++), the 
result can be partially delivered before the recursive call, in

x ++ (foldr (++) [] xs)

the whole list x has to be evaluated before the evaluation of foldr takes 
its next step.

But if 'f' is strict in its second argument, like for example (+) on Int, 
the recursive call has to be evaluated before the top level call to 'f' can 
be evaluated, so a stack of function calls has to be built before any 
evaluation of an 'f'-call can start, and that stack has to be unwound 
during the evaluation of the 'f'-calls from the innermost to the outermost.
That gives you two traversals: build stack, unwind.

In such cases, tail recursion (a left fold) is better because then the call 
to 'f' can be evaluated before the recursive call - but it has to be 
forced, or it will generate a thunk ((...(z `f` x1) ... ) `f` xn-1) `f` xn 
(and when that thunk is finally evaluated it nuilds a stack of 'f'-calls, 
which is then unwound, so you get three traversals: build thunk, thunk -> 
stack, unwind - unless 'f' is lazy in its first argument, like flip (++), 
then the thunk may be consumed without building the stack).

> 
> On Feb 3, 2012, at 5:36 AM, Chadda? Fouch? wrote:
> > let go a b = b `minus` (multiplies a c)
> > foldr go cs' (p:p':ps) ==> foldr go cs' (p':ps) `minus` multiplies p c
> > ==> (minus needs his first argument to start removing stuff) (foldr go
> > cs' ps `minus` multiplies p' c) `minus` multiplies p c
> > And so on and so forth...
> > In other words, contrary to your first version, this function must
> > develop the entire list before making its first suppression...
> > 
> > Your version rather correspond to a foldl (be careful of strictness,
> > using foldl it's pretty easy to get big thunks).
> > 
> > Foldr is very useful for functions that are lazy in their second
> > argument like (||) , (&&),  (:) or others but if the function is
> > strict in its second argument like yours (strict in b)...
> 
> Best regards,
> Zhi-Qiang Lei
> [email protected]



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

Message: 2
Date: Sun, 05 Feb 2012 14:40:21 +0100
From: "Henk-Jan van Tuyl" <[email protected]>
Subject: Re: [Haskell-beginners] numerical integration over lists
To: [email protected], "Thomas Engel" <[email protected]>
Message-ID: <[email protected]>
Content-Type: text/plain; charset=iso-8859-15; format=flowed;
        delsp=yes

On Sun, 05 Feb 2012 09:19:02 +0100, Thomas Engel <[email protected]>  
wrote:

> Hello,
>
> I have two list (one with x values, the other with y values)
> What I want to do is a numercial integration according the following  
> formula:
>
> Result x2 = Result x1 + ((y(x1) + y(x2))/2) * (x2 -x1)
>
> and put the result in another list.
>
> below my first try:
>
> integriereListe::(a)->(a)->(a)
> integriereListe [][]  = [0.0]
> integriereListe (x:xs) (y:ys)   = ((y - y2) /2) * (x2 -x)
>                                   where
>                                   x2 = head xs
>                                   y2 = head ys

The line
> integriereListe [][]  = [0.0]
should be
> integriereListe [][]  = 0.0
as the line below that calculates a number, not a list of numbers (that  
is, the type is different for that line).
You than need to correct the type of the function. Note, that you use  
'head' twice for lists that are empty at a certain point.

Regards,
Henk-Jan van Tuyl


-- 
http://Van.Tuyl.eu/
http://members.chello.nl/hjgtuyl/tourdemonad.html
Haskell programming
--



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

Message: 3
Date: Sun, 5 Feb 2012 17:03:46 +0200
From: Ovidiu Deac <[email protected]>
Subject: Re: [Haskell-beginners] yet another monad question
To: Chadda? Fouch? <[email protected]>
Cc: beginners <[email protected]>
Message-ID:
        <cakvse7sx3mhmnfw+rgsr-o8x2ofmjochgg6hlpuxrmy1e4d...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

thanks for the explanations! I guess it's clear now

On Sat, Feb 4, 2012 at 3:02 PM, Chadda? Fouch? <[email protected]>wrote:

> On Sat, Feb 4, 2012 at 12:05 PM, David McBride <[email protected]> wrote:
> > When you pass an argument to
> > readDir = findRegularFiles >>= readFiles
> >
> > it expands to
> > readDir arg = (findRegularFiles >>= readFiles) arg
> >
> > which fails because that expression takes no argument, only
> > findRegularFiles does.  Honestly I can't think of any way to get that
> > argument in there without explicitly naming it.
>
> I would say the problem is even before that, the expression
> "findRegularFiles >>= readFiles" is not well typed :
>
> (>>=) :: Monad m => m a -> (a -> m b) -> m b
> specialized here in :
> (>>=) :: IO a -> (a -> IO b) -> IO b
>
> but :
>
> findRegularFiles :: FilePath -> IO [FilePath]
>
> so findRegularFiles is not of type "IO a", so can't be the first
> argument of (>>=) (or the second of (=<<) since that's just the
> flipped version).
>
> But there is a solution ! What you're searching here is a function of type
> :
> ? :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c)
>
> A kind of monadic composition, there is an operator for that in
> Control.Monad since ghc 6.12 or even before :
>
> (>=>) :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c)
>
> so :
>
> > readDir = findRegularFiles >=> readFiles
>
> or
>
> > readDir = readFiles <=< findRegularFiles
>
> will work :)
>
> --
> Jeda?
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120205/be4c63ac/attachment-0001.htm>

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

Message: 4
Date: Sun, 5 Feb 2012 16:56:50 +0100
From: Thomas Engel <[email protected]>
Subject: Re: [Haskell-beginners] numerical integration over lists
To: Henk-Jan van Tuyl <[email protected]>
Cc: [email protected]
Message-ID: <20120205155650.GA2521@siduxbox>
Content-Type: text/plain; charset=us-ascii

Hello Henk-Jan,
> >
> 
> The line
> >integriereListe [][]  = [0.0]
> should be
> >integriereListe [][]  = 0.0
> as the line below that calculates a number, not a list of numbers
> (that is, the type is different for that line).
thanks for the hint. I have changed the function accordingly but there is still 
an error for the types.

integriereListe::(Float)->(Float)->(Float)
integriereListe [][]  = 0.0
integriereListe (x:xs) (y:ys)   = (y - y2) /2 * (x2 -x)
                                 where
                                 x2 = head xs
                                 y2 = head ys
 
 Couldn't match expected type `Float' with actual type `[t0]'
    In the pattern: x : xs
    In an equation for `integriereListe':
        integriereListe (x : xs) (y : ys)
          = (y - y2) / 2 * (x2 - x)
          where
              x2 = head xs
              y2 = head ys

This are my first steps in haskell. I don't know whether my first basic 
approach is OK or is there a better solution for this calculation?
There is no formula to map over a list and integrate, I only have two list with 
values. I can zip the lists together to have a list of tuples if this is an 
advantage.
What I need is the first and the second value from each list, do the 
calculation,
the second value will become the first value of the next calculation and so on 
until the end of the lists.
I also need the result of the last calculation to add to the current 
calculation.

My calculation in excel with VBA is working, but it's quite difficult for me to 
do this with functional programming.

Any hints are welcome!

Thomas




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

Message: 5
Date: Sun, 5 Feb 2012 16:05:35 +0000
From: Benjamin Edwards <[email protected]>
Subject: Re: [Haskell-beginners] numerical integration over lists
To: Thomas Engel <[email protected]>
Cc: [email protected]
Message-ID:
        <can6k4ngtwwsemxuqsj7dl-m-p70_3pv5inxmxv4dopwotom...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

The first two arguments to your function are not typed as lists in the
binding.

[Float] is a list of floats. (Float) is not.
On 5 Feb 2012 15:57, "Thomas Engel" <[email protected]> wrote:

> Hello Henk-Jan,
> > >
> >
> > The line
> > >integriereListe [][]  = [0.0]
> > should be
> > >integriereListe [][]  = 0.0
> > as the line below that calculates a number, not a list of numbers
> > (that is, the type is different for that line).
> thanks for the hint. I have changed the function accordingly but there is
> still an error for the types.
>
> integriereListe::(Float)->(Float)->(Float)
> integriereListe [][]  = 0.0
> integriereListe (x:xs) (y:ys)   = (y - y2) /2 * (x2 -x)
>                                 where
>                                 x2 = head xs
>                                 y2 = head ys
>
>  Couldn't match expected type `Float' with actual type `[t0]'
>    In the pattern: x : xs
>    In an equation for `integriereListe':
>        integriereListe (x : xs) (y : ys)
>          = (y - y2) / 2 * (x2 - x)
>          where
>              x2 = head xs
>              y2 = head ys
>
> This are my first steps in haskell. I don't know whether my first basic
> approach is OK or is there a better solution for this calculation?
> There is no formula to map over a list and integrate, I only have two list
> with values. I can zip the lists together to have a list of tuples if this
> is an advantage.
> What I need is the first and the second value from each list, do the
> calculation,
> the second value will become the first value of the next calculation and
> so on until the end of the lists.
> I also need the result of the last calculation to add to the current
> calculation.
>
> My calculation in excel with VBA is working, but it's quite difficult for
> me to do this with functional programming.
>
> Any hints are welcome!
>
> Thomas
>
>
> _______________________________________________
> Beginners mailing list
> [email protected]
> http://www.haskell.org/mailman/listinfo/beginners
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120205/33dd5d82/attachment-0001.htm>

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

Message: 6
Date: Sun, 5 Feb 2012 17:28:22 +0100
From: Daniel Fischer <[email protected]>
Subject: Re: [Haskell-beginners] numerical integration over lists
To: [email protected]
Cc: Thomas Engel <[email protected]>
Message-ID: <[email protected]>
Content-Type: Text/Plain;  charset="iso-8859-1"

On Sunday 05 February 2012, 16:56:50, Thomas Engel wrote:
> Hello Henk-Jan,
> 
> > The line
> > 
> > >integriereListe [][]  = [0.0]
> > 
> > should be
> > 
> > >integriereListe [][]  = 0.0
> > 
> > as the line below that calculates a number, not a list of numbers
> > (that is, the type is different for that line).
> 
> thanks for the hint. I have changed the function accordingly but there
> is still an error for the types.
> 
> integriereListe::(Float)->(Float)->(Float)

The type (Float) is just the type Float, the parentheses do nothing here. 
What you want the arguments to be is _lists of Float_, that is: [Float].
Now the question is whether you want the result to be a single number or a 
list, so the type should be one of

integriereListe :: [Float] -> [Float] -> Float

or

integriereListe :: [Float] -> [Float] -> [Float]


> integriereListe [][]  = 0.0

If you want a list as result, that should become [0.0].

> integriereListe (x:xs) (y:ys)   = (y - y2) /2 * (x2 -x)
>                                  where
>                                  x2 = head xs
>                                  y2 = head ys

Note that this will lead to an error call if eitherof the passed lists has 
only one element. Also your function definition doesn't treat the case that 
only one of the two arguments is nonempty.

> 
>  Couldn't match expected type `Float' with actual type `[t0]'
>     In the pattern: x : xs
>     In an equation for `integriereListe':
>         integriereListe (x : xs) (y : ys)
>           = (y - y2) / 2 * (x2 - x)

Should that be (y+y2)/2 ?

>           where
>               x2 = head xs
>               y2 = head ys
> 
> This are my first steps in haskell. I don't know whether my first basic
> approach is OK or is there a better solution for this calculation?
> There is no formula to map over a list and integrate, I only have two
> list with values. I can zip the lists together to have a list of tuples
> if this is an advantage. What I need is the first and the second value
> from each list, do the calculation, the second value will become the
> first value of the next calculation and so on until the end of the
> lists. I also need the result of the last calculation to add to the
> current calculation.

If I understand correctly, use

zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]

-- calculates the list of differences between successive elements,
-- differences [x1,x2,x3,...] = [x2-x1, x3-x2, ...]
--
-- We use subtract and don't swap the list arguments to zipWith
-- becuase this way there is no need to handle an empty list
-- specially, zipWith's definition lets (tail xs) unevaluated in that case.
--
differences :: Num a => [a] -> [a]
differences xs = zipWith subtract xs (tail xs)

areas :: Floating a => [a] -> [a] -> [a]
areas xs ys
    = zipWith (\dx dy -> dx * dy/2) (differences xs) (differences ys)

-- if it should have been (y+y2)/2 above, make that
-- sums ys, where sums ks = zipWith (+) ks
-- or areas xs ys = zipWith (*) (differenses xs) (means ys)
-- where means zs = map (/ 2) (sums zs)

and now, if you only wan the total,

area xs ys = sum (areas xs ys)

and if you want running sums

integrals xs ys = scanl (+) 0 (areas xs ys)

> 
> My calculation in excel with VBA is working, but it's quite difficult
> for me to do this with functional programming.
> 
> Any hints are welcome!
> 
> Thomas



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

_______________________________________________
Beginners mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 44, Issue 7
****************************************

Reply via email to