How to have multiple infinite ranges in list comprehensions?

生来就可爱ヽ(ⅴ<●) 提交于 2019-12-29 00:38:06

问题


In haskell I have a list comprehension like this:

sq = [(x,y,z) | x <- v, y <- v, z <- v, x*x + y*y == z*z, x < y, y < z]
    where v = [1..]

However when I try take 10 sq, it just freezes... Is there a way to handle multiple infinite ranges?

Thanks


回答1:


In addition to the other answers explaining the problem, here is an alternative solution, generalized to work with level-monad and stream-monad that lend themselves for searches over infinite search spaces (It is also compatible with the list monad and logict, but those won't play nicely with infinite search spaces, as you already found out):

{-# LANGUAGE MonadComprehensions #-}

module Triples where

import Control.Monad

sq :: MonadPlus m => m (Int, Int, Int)
sq = [(x, y, z) | x <- v, y <- v, z <- v, x*x + y*y == z*z, x < y, y < z]
    where v = return 0 `mplus` v >>= (return . (1+))

Now, for a fast breadth first search:

*Triples> :m +Control.Monad.Stream
*Triples Control.Monad.Stream> take 10 $ runStream sq
[(3,4,5),(6,8,10),(5,12,13),(9,12,15),(8,15,17),(12,16,20),(7,24,25),
(15,20,25),(10,24,26),(20,21,29)]

Alternatively:

*Triples> :m +Control.Monad.Levels
*Triples Control.Monad.Levels> take 5 $ bfs sq   -- larger memory requirements
[(3,4,5),(6,8,10),(5,12,13),(9,12,15),(8,15,17)]
*Triples Control.Monad.Levels> take 5 $ idfs sq  -- constant space, slower, lazy
[(3,4,5),(5,12,13),(6,8,10),(7,24,25),(8,15,17)]



回答2:


List comprehensions are translated into nested applications of the concatMap function:

concatMap :: (a -> [b]) -> [a] -> [b]
concatMap f xs = concat (map f xs)

concat :: [[a]] -> [a]
concat [] = []
concat (xs:xss) = xs ++ concat xss

-- Shorter definition:
--
-- > concat = foldr (++) []

Your example is equivalent to this:

sq = concatMap (\x -> concatMap (\y -> concatMap (\z -> test x y z) v) v) v
    where v = [1..]
          test x y z = 
              if x*x + y*y == z*z
              then if x < y
                   then if y < z
                        then [(x, y, z)]
                        else []
                   else []
              else []

This is basically a "nested loops" approach; it'll first try x = 1, y = 1, z = 1, then move on to x = 1, y = 1, z = 2 and so on, until it tries all of the list's elements as values for z; only then can it move on to try combinations with y = 2.

But of course you can see the problem—since the list is infinite, we never run out of values to try for z. So the combination (3, 4, 5) can only occur after infinitely many other combinations, which is why your code loops forever.

To solve this, we need to generate the triples in a smarter way, such that for any possible combination, the generator reaches it after some finite number of steps. Study this code (which handles only pairs, not triples):

-- | Take the Cartesian product of two lists, but in an order that guarantees
-- that all combinations will be tried even if one or both of the lists is 
-- infinite:
cartesian :: [a] -> [b] -> [(a, b)]
cartesian [] _ = []
cartesian _ [] = []
cartesian (x:xs) (y:ys) = 
    [(x, y)] ++ interleave3 vertical horizontal diagonal
        where 
          -- The trick is to split the problem into these four pieces:
          --
          -- |(x0,y0)| (x0,y1) ... horiz
          -- +-------+------------
          -- |(x1,y0)| .
          -- |   .   |  .
          -- |   .   |   .
          -- |   .   |    . 
          --   vert         diag
          vertical = map (\x -> (x,y)) xs
          horizontal = map (\y -> (x,y)) ys
          diagonal = cartesian xs ys


interleave3 :: [a] -> [a] -> [a] -> [a]
interleave3 xs ys zs = interleave xs (interleave ys zs)

interleave :: [a] -> [a] -> [a]
interleave xs [] = xs
interleave [] ys = ys
interleave (x:xs) (y:ys) = x : y : interleave xs ys

To understand this code (and fix it if I messed up!) look at this blog entry on how to count infinite sets, and at the fourth diagram in particular—the function is an algorithm based on that "zigzag"!

I just tried a simple version of your sq using this; it finds (3,4,5) almost instantly, but then takes very long to get to any other combination (in GHCI at least). But I think the key lessons to take away from this are:

  1. List comprehensions just don't work well for nested infinite lists.
  2. Don't spend too much time playing around with list comprehensions. Everything that they can do, functions like map, filter and concatMap can do—plus there are many other useful functions in the list library, so concentrate your effort on that.



回答3:


Your code freeze because yours predicate will never been satisfied.
Why ?

Let's take an example without any predicate to understand.

>>> let v = [1..] in take 10 $ [ (x, y, z) | x <- v,  y <- v, z <- v ] 
[(1,1,1),(1,1,2),(1,1,3),(1,1,4),(1,1,5),(1,1,6),(1,1,7),(1,1,8),(1,1,9),(1,1,10)]

As you see x and y will always be evaluated to 1 as z will never stop to rise.
Then your predicate can't be.

Any workaround ?

Try "Nested list" comprehension.

>>> [[ fun x y | x <- rangeX, predXY] | y  <- rangeY, predY ]   

Or parallel list comprehension which can be activated using,

>>> :set -XParallelListComp  

lookup on the doc




回答4:


This is possible, but you'll have to come up with an order in which to generate the numbers. The following generates the numbers you want; note that the x < y test can be replaced by generating only y that are >x and similarly for z (which is determined once x and y are bound):

[(x, y, z) | total <- [1..]
           , x <- [1..total-2]
           , y <- [x..total-1]
           , z <- [total - x - y]
           , x*x + y*y == z*z]


来源:https://stackoverflow.com/questions/15510916/how-to-have-multiple-infinite-ranges-in-list-comprehensions

标签
易学教程内所有资源均来自网络或用户发布的内容,如有违反法律规定的内容欢迎反馈
该文章没有解决你所遇到的问题?点击提问,说说你的问题,让更多的人一起探讨吧!