
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 but I got the failure Couldn't match type `[t0]' with `[[t0]]' In the pattern: y : ys In an equation for `integriereListe': integriereListe (x : xs) (y : ys) = ((y - y2) / 2) * (x2 - x) where x2 = head xs y2 = head ys another problem is how get the result x1 (see above) any hints are welcome. Thomas

On Sun, 05 Feb 2012 09:19:02 +0100, Thomas Engel
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 --

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).
Hello Henk-Jan, 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

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"
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).
Hello Henk-Jan, 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 Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hello Benjamin,
[Float] is a list of floats. (Float) is not.
thanks for pointing out an error. But now I get an other error message. integriereListe::[Float]->[Float]->[Float] integriereListe [][] = 0.0 integriereListe (x:xs) (y:ys) = (y - y2) / 2.0 * (x2 -x) where x2 = head xs y2 = head ys No instance for (Fractional [Float]) arising from a use of `/' Possible fix: add an instance declaration for (Fractional [Float]) In the first argument of `(*)', namely `(y - y2) / 2.0' In the expression: (y - y2) / 2.0 * (x2 - x) In an equation for `integriereListe': integriereListe (x : xs) (y : ys) = (y - y2) / 2.0 * (x2 - x) where x2 = head xs y2 = head ys Thomas

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

Hello Daniel, thank you very much for pointing out a solution.
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 Yes, you are right. That should be an sum instead of a difference.
-- sums ys, where sums ks = zipWith (+) ks -- or areas xs ys = zipWith (*) (differenses xs) (means ys) -- where means zs = map (/ 2) (sums zs)
I have changed the functions according your advice. But still I get an error: differences :: Num a => [a] -> [a] differences xs = zipWith subtract xs (tail xs) areas :: Floating a => [a] -> [a] -> [a] areas xs ys = zipWith (*) (differences xs) (means ys) where means zs = map (/ 2) (sums zs) where sums ks = zipWith (+) ks integrals xs ys = scanl (+) 0 (areas xs ys) Couldn't match expected type `[b0]' with actual type `[c0] -> [c0]' In the return type of a call of `sums' In the second argument of `map', namely `(sums zs)' In the expression: map (/ 2) (sums zs) Thomas

On Sunday 05 February 2012, 18:18:54, Thomas Engel wrote:
-- sums ys, where sums ks = zipWith (+) ks
Sigh, that's what you get for hopping to and fro while writing a mail. That should have been sums ks = zipWith (+) ks (tail ks) like for differences
-- or areas xs ys = zipWith (*) (differenses xs) (means ys) -- where means zs = map (/ 2) (sums zs)
I have changed the functions according your advice. But still I get an error:
differences :: Num a => [a] -> [a] differences xs = zipWith subtract xs (tail xs)
areas :: Floating a => [a] -> [a] -> [a] areas xs ys = zipWith (*) (differences xs) (means ys) where means zs = map (/ 2) (sums zs) where sums ks = zipWith (+) ks
It wasn't meant to be understood so, I intended differences etc. to be top- level functions, that's more readable.

Hello Daniel,
* Daniel Fischer
On Sunday 05 February 2012, 18:18:54, Thomas Engel wrote:
-- sums ys, where sums ks = zipWith (+) ks
Sigh, that's what you get for hopping to and fro while writing a mail. That should have been
sums ks = zipWith (+) ks (tail ks) it's working now
It wasn't meant to be understood so, I intended differences etc. to be top- level functions, that's more readable.
I have made an additional function for sums Thanks again Thomas
participants (4)
-
Benjamin Edwards
-
Daniel Fischer
-
Henk-Jan van Tuyl
-
Thomas Engel