How are dependent ranges computed in a list comprehension? - haskell

I'm currently making my way through Learn You a Haskell for Great Good!, and I'm confused on the penultimate example in Chapter 2.
As a way of generating triples representing all right triangles with all sides that are whole numbers less than or equal to 10, he gives this definition:
rightTriangles = [ (a,b,c) | c <- [1..10], b <- [1..c], a <- [1..b], a^2 + b^2 == c^2]
What I'm specifically confused about is the fact that b is bound to a list that ranges from 1 to c, and similarly with a. If my understanding is correct, c will be evaluated to all values in the list it is bound to, but I still don't see which value is being used for c in the range (e.g. all values of c, only the first c, etc.)
If it's not too much, a step by step explanation of how this evaluates would be great. :)
Thanks in advance!

Let's consider two simpler list comprehensions:
ex1 = [(a,b) | a <- [1..3], b <- [1..3]]
ex2 = [(a,b) | a <- [1..3], b <- [1..a]]
They're almost the same, but in the second case, b ranges from 1 to a, not 1 to 3. Let's consider what they're equal to; I've formatted their values in such a way as to make a point.
ex1 = [ (1,1), (1,2), (1,3)
, (2,1), (2,2), (2,3)
, (3,1), (3,2), (3,3) ]
ex2 = [ (1,1),
, (2,1), (2,2),
, (3,1), (3,2), (3,3) ]
In the first example, the list comprehension draws every possible combination of elements from [1..3] and [1..3]. But since we're talking about lists, not sets, the order it does that in is important. Thus, in more detail, what ex1 really means is this:
Let a be equal to every possible value from its list.
For each value of a, let b be every possible value from its list.
(a,b) is an element of the output list
Or, rephrased: "for every possible value of a, compute (a,b) for every possible value of b." If you look at the order of the results, this is what happens:
For the first three elements, a is equal to 1, and we see it paired with every value of b.
For the next three elements, a is equal to 2, and we see every value of b.
And finally, for the last three elements, a is equal to 3 and we see every value of b.
In the second case, much the same thing happens. But because a is picked first, b can depend on it. Thus:
First, a is equal to 1, and we see it paired with every possible value of b. Since b <- [1..a], that means b <- [1..1], and so there's only one option.
After one element, then, a is equal to 2, and we see that paired with every possible value of b. Now that means b <- [1..2], and so we get two results.
Finally, a is equal to 3, and so we're picking b <- [1..3]; this gives us the full set of three results.
In other words, because the list comprehensions rely on an ordering, you can take advantage of that. One way to see that is to imagine translating these list comprehensions into nested list comprehensions:
ex1 = concat [ [(a,b) | b <- [1..3]] | a <- [1..3] ]
ex2 = concat [ [(a,b) | b <- [1..a]] | a <- [1..3] ]
To get the right behavior, a <- [1..3] must go on the outside; this ensures that the bs change faster than the as. And it hopefully makes it clear how b can depend on a. Another translation (basically the one used in the Haskell 2010 Report) would be:
ex1 = concatMap (\a -> [(a,b) | b <- [1..3]]) [1..3]
= concatMap (\a -> concatMap (\b -> [(a,b)]) [1..3]) [1..3]
ex2 = concatMap (\a -> [(a,b) | b <- [1..a]]) [1..3]
= concatMap (\a -> concatMap (\b -> [(a,b)]) [1..a]) [1..3]
Again, this makes the nesting very explicit, even if it's hard to follow. Something to keep in mind is that if the selection of a is to happen first, it must be on the outside of the translated expression, even though it's on the inside of the list comprehension. The full, formal translation of rightTriangles would then be
rightTriangles =
concatMap (\c ->
concatMap (\b ->
concatMap (\a ->
if a^2 + b^2 == c^2
then [(a,b,c)]
else []
) [1..b]
) [1..c]
) [1..10]
As a side note, another way to write rightTriangles is as follows:
import Control.Monad (guard)
rightTriangles = do c <- [1..10]
b <- [1..c]
a <- [1..b]
guard $ a^2 + b^2 == c^2
return (a,b,c)
You probably haven't used do notation yet, and certainly not for anything but IO, so I'm not saying you should necessarily understand this. But you can read the x <- list lines as saying "for each x in list", and so read this as a nested loop:
rightTriangles = do
c <- [1..10] -- For each `c` from `1` to `10`, ...
b <- [1..c] -- For each `b` from `1` to `c`, ...
a <- [1..b] -- For each `a` from `1` to `b`, ...
guard $ a^2 + b^2 == c^2 -- If `a^2 + b^2 /= c^2`, then `continue` (as in C);
return (a,b,c) -- `(a,b,c)` is the next element of the output list.
Note that the continue only skips to the next iteration of the innermost loop in this interpretation. You could also write it as
rightTriangles = do c <- [1..10]
b <- [1..c]
a <- [1..b]
if a^2 + b^2 == c^2
then return (a,b,c)
else [] -- or `mzero`
Where the last lines say "if a^2 + b^2 == c^2, add (a,b,c) to the output list; otherwise, add nothing." I only mention this because I thought seeing it written this way might help make the "nested loop"-type structure that's going on clear, not because you should fully understand do-notation while reading Chapter 2 of Learn You A Haskell :-)

Seeing you have experience with imperative programming, a short answer would be: similar to this for nesting (pseudo code):
for(c = 1; c <= 10; c++) {
for(b = 1; b <= c; b++) {
for(a = 1; a <= b; a++) {
if(a ^ 2 + b ^ 2 == c ^ 2) {
list.append((a, b, c));
}
}
}
}

Related

Dovetail iteration over infinite lists in Haskell

I want to iterate 2 (or 3) infinite lists and find the "smallest" pair that satisfies a condition, like so:
until pred [(a,b,c) | a<-as, b<-bs, c<-cs]
where pred (a,b,c) = a*a + b*b == c*c
as = [1..]
bs = [1..]
cs = [1..]
The above wouldn't get very far, as a == b == 1 throughout the run of the program.
Is there a nice way to dovetail the problem, e.g. build the infinite sequence [(1,1,1),(1,2,1),(2,1,1),(2,1,2),(2,2,1),(2,2,2),(2,2,3),(2,3,2),..] ?
Bonus: is it possible to generalize to n-tuples?
There's a monad for that, Omega.
Prelude> let as = each [1..]
Prelude> let x = liftA3 (,,) as as as
Prelude> let x' = mfilter (\(a,b,c) -> a*a + b*b == c*c) x
Prelude> take 10 $ runOmega x'
[(3,4,5),(4,3,5),(6,8,10),(8,6,10),(5,12,13),(12,5,13),(9,12,15),(12,9,15),(8,15,17),(15,8,17)]
Using it's applicative features, you can generalize to arbitrary tuples:
quadrupels = (,,,) <$> as <*> as <*> as <*> as -- or call it liftA4
But: this alone does not eliminate duplication, of course. It only gives you proper diagonalization. Maybe you could use monad comprehensions together with an approach like Thomas's, or just another mfilter pass (restricting to b /= c, in this case).
List comprehensions are great (and concise) ways to solve such problems. First, you know you want all combinations of (a,b,c) that might satisfy a^2 + b^2 = c^2 - a helpful observation is that (considering only positive numbers) it will always be the case that a <= c && b <= c.
To generate our list of candidates we can thus say c ranges from 1 to infinity while a and b range from one to c.
[(a,b,c) | c <- [1..], a <- [1..c], b <- [1..c]]
To get to the solution we just need to add your desired equation as a guard:
[(a,b,c) | c <- [1..], a <- [1..c], b <- [1..c], a*a+b*b == c*c]
This is inefficient, but the output is correct:
[(3,4,5),(4,3,5),(6,8,10),(8,6,10),(5,12,13),(12,5,13),(9,12,15)...
There are more principled methods than blind testing that can solve this problem.
{- It depends on what is "smallest". But here is a solution for a concept of "smallest" if tuples were compared first by their max. number and then by their total sum. (You can just copy and paste my whole answer into a file as I write the text in comments.)
We will need nub later. -}
import Data.List (nub)
{- Just for illustration: the easy case with 2-tuples. -}
-- all the two-tuples where 'snd' is 'n'
tuples n = [(i, n) | i <- [1..n]]
-- all the two-tuples where 'snd' is in '1..n'
tuplesUpTo n = concat [tuples i | i <- [1..n]]
{-
To get all results, you will need to insert the flip of each tuple into the stream. But let's do that later and generalize first.
Building tuples of arbitrary length is somewhat difficult, so we will work on lists. I call them 'kList's, if they have a length 'k'.
-}
-- just copied from the tuples case, only we need a base case for k=1 and
-- we can combine all results utilizing the list monad.
kLists 1 n = [[n]]
kLists k n = do
rest <- kLists (k-1) n
add <- [1..head rest]
return (add:rest)
-- same as above. all the klists with length k and max number of n
kListsUpTo k n = concat [kLists k i | i <- [1..n]]
-- we can do that unbounded as well, creating an infinite list.
kListsInf k = concat [kLists k i | i <- [1..]]
{-
The next step is rotating these lists around, because until now the largest number is always in the last place. So we just look at all rotations to get all the results. Using nub here is admittedly awkward, you can improve that. But without it, lists where all elements are the same are repeated k times.
-}
rotate n l = let (init, end) = splitAt n l
in end ++ init
rotations k l = nub [rotate i l | i <- [0..k-1]]
rotatedKListsInf k = concatMap (rotations k) $ kListsInf k
{- What remains is to convert these lists into tuples. This is a bit awkward, because every n-tuple is a separate type. But it's straightforward, of course. -}
kListToTuple2 [x,y] = (x,y)
kListToTuple3 [x,y,z] = (x,y,z)
kListToTuple4 [x,y,z,t] = (x,y,z,t)
kListToTuple5 [x,y,z,t,u] = (x,y,z,t,u)
kListToTuple6 [x,y,z,t,u,v] = (x,y,z,t,u,v)
{- Some tests:
*Main> take 30 . map kListToTuple2 $ rotatedKListsInf 2
[(1,1),(1,2),(2,1),(2,2),(1,3),(3,1),(2,3),(3,2),(3,3),(1,4),(4,1),(2,4),(4,2),(3,4),
(4,3),(4,4),(1,5),(5,1),(2,5),(5,2),(3,5),(5,3),(4,5),(5,4),(5,5),(1,6),(6,1),
(2,6), (6,2), (3,6)]
*Main> take 30 . map kListToTuple3 $ rotatedKListsInf 3
[(1,1,1),(1,1,2),(1,2,1),(2,1,1),(1,2,2),(2,2,1),(2,1,2),(2,2,2),(1,1,3),(1,3,1),
(3,1,1),(1,2,3),(2,3,1),(3,1,2),(2,2,3),(2,3,2),(3,2,2),(1,3,3),(3,3,1),(3,1,3),
(2,3,3),(3,3,2),(3,2,3),(3,3,3),(1,1,4),(1,4,1),(4,1,1),(1,2,4),(2,4,1),(4,1,2)]
Edit:
I realized there is a bug: Just rotating the ordered lists isn't enough of course. The solution must be somewhere along the lines of having
rest <- concat . map (rotations (k-1)) $ kLists (k-1) n
in kLists, but then some issues with repeated outputs arise. You can figure that out, I guess. ;-)
-}
It really depends on what you mean by "smallest", but I assume you want to find a tuple of numbers with respect to its maximal element - so (2,2) is less than (1,3) (while standard Haskell ordering is lexicographic).
There is package data-ordlist, which is aimed precisely at working with ordered lists. It's function mergeAll (and mergeAllBy) allows you to combine a 2-dimensional matrix ordered in each direction into an ordered list.
First let's create a desired comparing function on tuples:
import Data.List (find)
import Data.List.Ordered
compare2 :: (Ord a) => (a, a) -> (a, a) -> Ordering
compare2 x y = compare (max2 x, x) (max2 y, y)
where
max2 :: Ord a => (a, a) -> a
max2 (x, y) = max x y
Then using mergeAll we create a function that takes a comparator, a combining function (which must be monotonic in both arguments) and two sorted lists. It combines all possible elements from the two lists using the function and produces a result sorted list:
mergeWith :: (b -> b -> Ordering) -> (a -> a -> b) -> [a] -> [a] -> [b]
mergeWith cmp f xs ys = mergeAllBy cmp $ map (\x -> map (f x) xs) ys
With this function, it's very simple to produce tuples ordered according to their maximum:
incPairs :: [(Int,Int)]
incPairs = mergeWith compare2 (,) [1..] [1..]
Its first 10 elements are:
> take 10 incPairs
[(1,1),(1,2),(2,1),(2,2),(1,3),(2,3),(3,1),(3,2),(3,3),(1,4)]
and when we (for example) look for the first pair whose sum of squares is equal to 65:
find (\(x,y) -> x^2+y^2 == 65) incPairs
we get the correct result (4,7) (as opposed to (1,8) if lexicographic ordering were used).
This answer is for a more general problem for a unknown predicate. If the predicate is known, more efficient solutions are possible, like others have listed solutions based on knowledge that you don't need to iterate for all Ints for a given c.
When dealing with infinite lists, you need to perform breadth-first search for solution. The list comprehension only affords depth-first search, that is why you never arrive at a solution in your original code.
counters 0 xs = [[]]
counters n xs = concat $ foldr f [] gens where
gens = [[x:t | t <- counters (n-1) xs] | x <- xs]
f ys n = cat ys ([]:n)
cat (y:ys) (x:xs) = (y:x): cat ys xs
cat [] xs = xs
cat xs [] = [xs]
main = print $ take 10 $ filter p $ counters 3 [1..] where
p [a,b,c] = a*a + b*b == c*c
counters generates all possible counters for values from the specified range of digits, including a infinite range.
First, we obtain a list of generators of valid combinations of counters - for each permitted digit, combine it with all permitted combinations for counters of smaller size. This may result in a generator that produces a infinite number of combinations. So, we need to borrow from each generator evenly.
So gens is a list of generators. Think of this as a list of all counters starting with one digit: gens !! 0 is a list of all counters starting with 1, gens !! 1 is a list of all counters starting with 2, etc.
In order to borrow from each generator evenly, we could transpose the list of generators - that way we would get a list of first elements of the generators, followed by a list of second elements of the generators, etc.
Since the list of generators may be infinite, we cannot afford to transpose the list of generators, because we may never get to look at the second element of any generator (for a infinite number of digits we'd have a infinite number of generators). So, we enumerate the elements from the generators "diagonally" - take first element from the first generator; then take the second element from the first generator and the first from the second generator; then take the third element from the first generator, the second from the second, and the first element from the third generator, etc. This can be done by folding the list of generators with a function f, which zips together two lists - one list is the generator, the other is the already-zipped generators -, the beginning of one of them being offset by one step by adding []: to the head. This is almost zipWith (:) ys ([]:n) - the difference is that if n or ys is shorter than the other one, we don't drop the remainder of the other list. Note that folding with zipWith (:) ys n would be a transpose.
For this answer I will take "smallest" to refer to the sum of the numbers in the tuple.
To list all possible pairs in order, you can first list all of the pairs with a sum of 2, then all pairs with a sum of 3 and so on. In code
pairsWithSum n = [(i, n-i) | i <- [1..n-1]]
xs = concatMap pairsWithSum [2..]
Haskell doesn't have facilities for dealing with n-tuples without using Template Haskell, so to generalize this you will have to switch to lists.
ntuplesWithSum 1 s = [[s]]
ntuplesWithSum n s = concatMap (\i -> map (i:) (ntuplesWithSum (n-1) (s-i))) [1..s-n+1]
nums n = concatMap (ntuplesWithSum n) [n..]
Here's another solution, with probably another slightly different idea of "smallest". My order is just "all tuples with max element N come before all tuples with max element N+1". I wrote the versions for pairs and triples:
gen2_step :: Int -> [(Int, Int)]
gen2_step s = [(x, y) | x <- [1..s], y <- [1..s], (x == s || y == s)]
gen2 :: Int -> [(Int, Int)]
gen2 n = concatMap gen2_step [1..n]
gen2inf :: [(Int, Int)]
gen2inf = concatMap gen2_step [1..]
gen3_step :: Int -> [(Int, Int, Int)]
gen3_step s = [(x, y, z) | x <- [1..s], y <- [1..s], z <- [1..s], (x == s || y == s || z == s)]
gen3 :: Int -> [(Int, Int, Int)]
gen3 n = concatMap gen3_step [1..n]
gen3inf :: [(Int, Int, Int)]
gen3inf = concatMap gen3_step [1..]
You can't really generalize it to N-tuples, though as long as you stay homogeneous, you may be able to generalize it if you use arrays. But I don't want to tie my brain into that knot.
I think this is the simplest solution if "smallest" is defined as x+y+z because after you find your first solution in the space of Integral valued pythagorean triangles, your next solutions from the infinite list are bigger.
take 1 [(x,y,z) | y <- [1..], x <- [1..y], z <- [1..x], z*z + x*x == y*y]
-> [(4,5,3)]
It has the nice property that it returns each symmetrically unique solution only once. x and z are also infinite, because y is infinite.
This does not work, because the sequence for x never finishes, and thus you never get a value for y, not to mention z. The rightmost generator is the innermost loop.
take 1 [(z,y,x)|z <- [1..],y <- [1..],x <- [1..],x*x + y*y == z*z]
Sry, it's quite a while since I did haskell, so I'm going to describe it with words.
As I pointed out in my comment. It is not possible to find the smallest anything in an infinite list, since there could always be a smaller one.
What you can do is, have a stream based approach that takes the lists and returns a list with only 'valid' elements, i. e. where the condition is met. Lets call this function triangle
You can then compute the triangle list to some extent with take n (triangle ...) and from this n elements you can find the minium.

Having trouble understanding list comprehensions

I've just started learning haskell(literally, tonight!) and I'm having a little trouble understanding the logic of list comprehensions, more specifically the <- operator. A little example on Learn You Some Haskell Finds all tuples that have a length less than 10:
ghci> let triangles = [ (a,b,c) | c <- [1..10], b <- [1..10], a <- [1..10] ]
my initial understanding was that these would all increment together, but after seeing the output I really dont understanding the incrementing method for these lists. Another example that seems to get me is:
ghci> let rightTriangles = [ (a,b,c) | c <- [1..10], b <- [1..c], a <- [1..b], a^2 + b^2 == c^2]
I would really appreciate a little explanation on these, thanks for your patience with my lack of haskell intelligence.
Read [ as "list of", | as "for", <- as "in", , as "and".
The enumerations are done in nested fashion. [ (a,b,c) | c <- [1..10], b <- [1..c], a <- [1..b], a^2 + b^2 == c^2] is really
for c from 1 to 10 step 1:
for b from 1 to c step 1:
for a from 1 to b step 1:
if (a^2 + b^2 == c^2):
emit (a,b,c)
In Haskell though, the above is achieved by the following translation
[1..10] >>= (\c-> -- (a function of 'c', producing ...
[1..c] >>= (\b-> -- (a function of 'b', producing ...
[1..b] >>= (\a-> -- (a function of 'a', producing ...
if a^2+b^2==c^2 then [(a,b,c)] else []
-- or: [(a,b,c) | a^2+b^2==c^2]
)))
so you really can see the nested structure here. (>>=) is nothing mysterious too. Read >>= as "fed into" or "pushed through", although its official name is "bind". It is defined (for lists) as
(xs >>= f) = concatMap f xs = concat (map f xs)
f here is called (by map) upon each element of xs, in order. It must produce lists so that they could be combined with concat. Since empty lists [] are eliminated on concat (e.g. concat [[1], [], [3]] == [1,3]) all the elements that do not pass the test are eliminated from the final output.
For the full translation see section 3.11, List Comprehensions, of the Haskell 98 Report. In general a list comprehension may contain a pattern, not just a variable name. The comprehension
[e | pat <- ls, ...]
is translated as
ls >>= (\x -> case x of pat -> [e | ...] ;
_ -> [] )
where pat is some pattern, and x is a fresh variable. When there's a pattern mismatch, an empty list is produced (instead of a run-time error), and that element x of ls is skipped over. This is useful for additional pattern-based filtering, like e.g. [x | Just x <- ls, even x] where all the Nothings in ls are quietly ignored.
[ (a,b,c) | c <- [1..10], b <- [1..10], a <- [1..10] ] means, for all combinations of (a,b,c) where a is in [1..10], b is in [1..10], c is in [1..10]
If you want the (1,1,1) (2,2,2) kinds, you should use zip: zip [1..10] [1..10] or for 3 lists, zip3 [1..10] [1..10] [1..10]
I think of list comprehension syntax as Haskell's attempt to get Set-builder notation in the language. We use '[' rather than '{' and '<-' rather than '∈'. List comprehension syntax can even be generalized to arbitrary monads.

Understanding A bit of Haskell

I have a quick question about Haskell. I've been following Learn You a Haskell, and am just a bit confused as to the execution order / logic of the following snippet, used to calculate the side lengths of a triangle, when all sides are equal to or less than 10 and the total perimeter of the triangle is 24:
[(a,b,c) | c <- [1..10], b <- [1..c], a <- [1..b], a^2 + b^2 == c^2, a+b+c==24]
The part that is confusing to me is the upper expansion bound on the b and a binding. From what I gather, the ..c and ..b are used to remove additional permutations (combinations?) of the same set of triangle sides.
When I run it with the ..c/b, I get the answer:
[(6,8,10)]
When I don't have the ..c/b:
[(a,b,c) | c <- [1..10], b <- [1..10], a <- [1..10], a^2 + b^2 == c^2, a+b+c==24]
as I didn't when I initially typed it in, I got:
[(8,6,10),(6,8,10)]
Which is obviously representative of the same triangle, save for the a and b values have been swapped.
So, can someone walk me through the logic / execution / evaluation of what's going on here?
The original version considers all triplets (a,b,c) where c is a number between 1 and 10, b is a number between 1 and c and a is a number between 1 and b. (6,8,10) fits that criteria, (8,6,10) doesn't (because here a is 8 and b is 6, so a isn't between 0 and 6).
In your version you consider all triplets (a,b,c) where a, b and c are between 1 and 10. You make no restrictions on how a, b and c relate to each other, so (8, 6, 10) is not excluded since all numbers in it are indeed between 1 and 10.
If you think of it in terms of imperative for-loops, your version does this:
for c from 1 to 10:
for b from 1 to 10:
for a from 1 to 10:
if a^2 + b^2 == c^2 and a+b+c==24:
add (a,b,c) to the result
while the original version does this:
for c from 1 to 10:
for b from 1 to c:
for c from 1 to b:
if a^2 + b^2 == c^2 and a+b+c==24:
add (a,b,c) to the result
It's not about execution order. In the first example you don't see the degenerate solution
[(8,6,10)]
since a <= b <= c. In the second case a > b is included in the list comprehension.
List comprehensions can be written in terms of other functions like concatMap, which clarifies the scope of the bindings. As a one-liner, your example becomes something like this:
concatMap (\c -> concatMap (\b -> concatMap (\a -> if a^2 + b^2 == c^2 then (if a+b+c == 24 then [(a,b,c)] else []) else []) (enumFromTo 1 b)) (enumFromTo 1 c)) (enumFromTo 1 10)
Yeah, that looks ugly, but it's similar to what Haskell desugars your comprehensions into. The scope of each of the variables a, b and c, should be obvious from this.
Or alternatively, this can be written with the List monad:
import Control.Monad
example = do c <- [1..10]
b <- [1..c]
a <- [1..b]
guard (a^2 + b^2 == c^2)
guard (a+b+c == 24)
return (a,b,c)
This is actually very similar as the one-liner above, given the definition of the List Monad and guard:
instance Monad [] where
return x = [x]
xs >>= f = concatMap f xs
instance MonadPlus [] where
mzero = []
mconcat = (++)
guard bool = if bool then return () else mzero

Why can't a list be defined like this in Haskell?

[(a,b) | a <- [1..5], b <- [1..5], a+b <- [1..10] ]
Trying to define define a list that follows these rules. I know it doesn't allow the way I am adding a and b but I don't understand why.
Edited forgot the "<-"
Maybe you want this?
[(a,b) | a <- [1..5], b <- [1..5], a + b >= 1 && a + b <= 10]
Or this?
[(a,b) | a <- [1..5], b <- [1..5], a + b `elem` [1..10]]
Haskell doesn't solve equations for you, it performs calculations.
This declares the values which a variable takes:
a <- [1..5]
This is a request for Haskell to solve an equation, which it doesn't do... the left side has to be a valid pattern.
a + b <- [1..10] # Not valid Haskell
Of course, patterns can be more sophisticated,
> [a | Just a <- [Just 10, Nothing, Just 20]]
[10, 20]
The "<-" in a list comprehension actually draws elements from a list.
Your third expression, "a+b <- [1..10]" is really trying to express that the sum could be drawn from a list. That's a job for (elem), a predicate, or test.
elem :: (Eq a) => a -> [a] -> Bool
A pretty good way to think about the problem is, how would it be implemented? You'd have to take elements, then test to see if they met the criteria. I'd use a predicate like
elem (a + b) [1..10]
to test that.

Pythagorean triple in Haskell without symmetrical solutions

I gotta do the Pythagorean triple in Haskell without symmetrical solutions. My try is:
terna :: Int -> [(Int,Int,Int)]
terna x = [(a,b,c)|a<-[1..x], b<-[1..x], c<-[1..x], (a^2)+(b^2) == (c^2)]
and I get as a result:
Main> terna 10
[(3,4,5),(4,3,5),(6,8,10),(8,6,10)]
As you can see, I´m getting symmetrical solutions like: (3,4,5) (4,3,5). I need to get rid of them but I don´t know how. Can anyone help me?
Every time you have a duplicate you have one version in which a is greater than b and one where b is greater than a. So if you want to make sure you only ever get one of them, you just need to make sure that either a is always equal to or less than b or vice versa.
One way to achieve this would be to add it as a condition to the list comprehension.
Another, more efficient way, would be to change b's generator to b <- [1..a], so it only generates values for b which are smaller or equal to a.
Speaking of efficiency: There is no need to iterate over c at all. Once you have values for a and b, you could simply calculate (a^2)+(b^2) and check whether it has a natural square root.
Don't know Haskell at all (perhaps you're learning it now?) but it seems like you could get rid of them if you could take only the ones for which a is less than or equal to b. That would get rid of the duplicates.
Try with a simple recursive generator:
http://en.wikipedia.org/wiki/Formulas_for_generating_Pythagorean_triples
(new article)
http://en.wikipedia.org/wiki/Tree_of_primitive_Pythagorean_triples
EDIT (7 May 2014)
Here I have made infinite generator that can generate primitive triplets ordered by perimeter (but can be modified to be ordered by other parameter - hypotenuses, area, ...) as long as it holds that any triplet is smaller that any generated from generator matrix according to provided compare function
import Data.List -- for mmult
merge f x [] = x
merge f [] y = y
merge f (x:xs) (y:ys)
| f x y = x : merge f xs (y:ys)
| otherwise = y : merge f (x:xs) ys
mmult :: Num a => [[a]] -> [[a]] -> [[a]]
mmult a b = [ [ sum $ zipWith (*) ar bc | bc <- (transpose b) ] | ar <- a ]
tpgen_matrix = [[[ 1,-2, 2],[ 2 ,-1, 2],[ 2,-2, 3]],
[[ 1, 2, 2],[ 2 , 1, 2],[ 2, 2, 3]],
[[-1, 2, 2],[-2 , 1, 2],[-2, 2, 3]]]
matrixsum = sum . map sum
tripletsorter x y = ( matrixsum x ) < ( matrixsum y ) -- compare perimeter
triplegen_helper b = foldl1
( merge tripletsorter )
[ h : triplegen_helper h | x <- tpgen_matrix , let h = mmult x b ]
triplets = x : triplegen_helper x where x = [[3],[4],[5]]
main = mapM print $ take 10 triplets
You can do the following:
pythagorean = [ (x,y,m*m+n*n) |
m <- [2..],
n <- [1 .. m-1],
let x = m*m-n*n,
let y = 2*m*n ]
This might work: Got it from this tutorial
triangles x = [(a,b,c) | c <- [1..x], b <- [1..c], a <- [1..b] , a^2 + b^2 == c^2]
List comprehension syntax makes this easy:
triplets :: Integer -> [(Integer, Integer, Integer)]
triplets d = [(a,b,c) | a <- [1..d], b <- [a..d], c <- [b..d], a^2 + b^2 == c^2]
This basically says than we build a list from as,bs and cs, where a changes from 1 to d, b changes from current a to d and etc. It also says that a^2 + b^2 == c^2 should hold.

Resources