[Haskell-cafe] list comprehension doesn't work
Mark Lentczner
mark.lentczner at gmail.com
Tue May 14 23:13:09 CEST 2013
module Stuff where
import Data.List
-- Let's translate your specification directly into a list comprehension
s1 :: [(Integer, Integer)]
s1 = [(x,y)
| x <- [1..] -- for this problem, better to have 0 ∉ N
, let a = 1 -- if 1 ∈ N,
, let b = x -- then by setting a = 1 and b = x
, x == a * b -- we can have any x ∈ N, x = a · b, where a, b
∈ N
, x > 5
, x < 500
, c <- [1..] -- this is a problem, see below
, let y = c * c
, y <= 1000
, y `mod` x == 0
]
-- Something is wrong with the a*b constraint as specified, since it has no
-- effect. I bet the intention was that x is a composite number, not prime.
-- We could insert a primality test, but it is easier to construct all
possible
-- x values that are clearly the composite of two numbers greater than 1:
s2 :: [(Integer, Integer)]
s2 = [(x,y)
| a <- [2..499] -- we know the upper bound
, b <- [2..a] -- a 'diagonalization', since one of the two
numbers
, let x = a * b -- must be same or smaller, let it be b
, x > 5
, x < 500
, c <- [1..] -- still a problem
, let y = c * c
, y < 1000
, y `mod` x == 0
]
-- Let's fix the problem of having an infinite source in the middle of the
-- the comprehension.
--
-- To understand the problem, think about how the comprehension is
evaluated.
-- The whole expression after the vertical bar is a value in the list monad.
-- You can think of each comma separated term being handled left to right.
If
-- the term is an <-, then one value from the list is bound to the variable
-- on the right, and the next term considered. If the term is a let, then it
-- is just a binding. Finally, if the term is a condition, then if it holds,
-- it goes on, otherwise it "backtracks". If the end of the term list is
reached
-- then the expression before the vertical bar as produced as a value in the
-- result list... and then we "backtrack". Backtracking has the effect of
-- backing up to the previous <- and binding the next value in that list. If
-- it runs out, then backtrack further.
--
-- The problem is that if there is an infinite list in the middle of the
-- comprehension, evaluation will never backtrack before it, as that list
-- never ends. And hence, any prior <- will never bind its next value.
--
-- The fix is to have only finite lists in the middle. Here, we can fix
-- an upper bound to c.
s3 :: [(Integer, Integer)]
s3 = [(x,y)
| a <- [2..499]
, b <- [2..a]
, let x = a * b
, x > 5
, x < 500
, c <- [1..floor(sqrt 1000 :: Double)]
, let y = c * c
, y `mod` x == 0
]
-- The above will produce duplicates because there may be more than one way
-- to produce a value x as the product of two values a and b. We can easily
-- de-duplicate them with the library function nub:
s4 :: [(Integer, Integer)]
s4 = nub s3
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20130514/1a81c364/attachment-0001.htm>
More information about the Haskell-Cafe
mailing list